SlideShare ist ein Scribd-Unternehmen logo
1 von 29
Downloaden Sie, um offline zu lesen
Constraint Programming in Haskell
Melbourne Haskell Users Group
David Overton
29 October 2015
Table of Contents
1 Constraint programming
2 Constraint logic programming
3 Finite domain constraints
4 Constraint programming in Haskell
Basic equality and inequality
Arithmetic expressions
5 Conclusion
Constraint programming
Constraint programming is a declarative programming paradigm for solving constraint
satisfaction problems.
• A set of constraint variables over a domain, e.g. Booleans, integers, reals, finite
domain.
• A set of constraints between those variables.
• A solver to find solutions to the constraints, i.e. assignments of variables to values
in the domain such that all constraints are satisfied.
Applications: planning, scheduling, resource allocation, computer graphics, digital
circuit design, programming language analysis, . . .
Table of Contents
1 Constraint programming
2 Constraint logic programming
3 Finite domain constraints
4 Constraint programming in Haskell
Basic equality and inequality
Arithmetic expressions
5 Conclusion
Constraint logic programming
• Constraint programming and logic programming work well together.
• Many Prolog implementations have built in constraint solvers.
• Basic idea:
• add constraints to the constraint store
• constraint solver works behind the scenes to propagate constraints
• use Prolog’s backtracking search mechanism to generate solutions
• Advantages over pure logic programming:
• “constrain-and-generate” rather than “generate-and-test”
• constraint solver can greatly reduce the search space required compared to Prolog’s
built-in depth-first-search
• much more powerful than relying on just unification and backtracking
Table of Contents
1 Constraint programming
2 Constraint logic programming
3 Finite domain constraints
4 Constraint programming in Haskell
Basic equality and inequality
Arithmetic expressions
5 Conclusion
Finite domain constraints
• One of the most widely used varieties of constraint solver.
• Variables range over a finite domain of integers.
• Simple equality and inequality constraints: =, =, <, >, ≤, ≥
• Also simple arithmetic expressions: +, −, ×, abs
Arc consistency
Solver uses an arc consistency algorithm, e.g. AC-3
• Constraint store holds the set of constraints to be checked.
• For each constraint, the domains of the variables involved are checked to ensure
they are consistent with the contraint.
• Any values in the domains that break consistency are removed.
• If the domain of a variable changes then all other constraints involving that
variable are rechecked.
Example
x ∈ {1, 2, 3} ∧ y ∈ {1, 2, 3}
add constraint x < y
⇒ x ∈ {1, 2} ∧ y ∈ {2, 3}
add constraint y = 2
⇒ x ∈ {1} ∧ y ∈ {2}
Example: n queens in SWI-Prolog
n_queens(N, Qs) :-
length(Qs, N),
Qs ins 1..N,
safe_queens(Qs).
safe_queens([]).
safe_queens([Q|Qs]) :-
safe_queen(Qs, Q, 1),
safe_queens(Qs).
safe_queen([], _, _).
safe_queen([Q|Qs], Q0, D0) :-
Q0 #= Q,
abs(Q0 - Q) #= D0,
D1 #= D0 + 1,
safe_queen(Qs, Q0, D1).
Table of Contents
1 Constraint programming
2 Constraint logic programming
3 Finite domain constraints
4 Constraint programming in Haskell
Basic equality and inequality
Arithmetic expressions
5 Conclusion
Constraint programming in Haskell
How can we do something similar in Haskell? Use a monad!
Example: n queens in SWI-Prolog and Haskell
n_queens(N, Qs) :-
length(Qs, N),
Qs ins 1..N,
safe_queens(Qs).
safe_queens([]).
safe_queens([Q|Qs]) :-
safe_queen(Qs, Q, 1),
safe_queens(Qs).
safe_queen([], _, _).
safe_queen([Q|Qs], Q0, D0) :-
Q0 #= Q,
abs(Q0 - Q) #= D0,
D1 #= D0 + 1,
safe_queen(Qs, Q0, D1).
nQueens :: Int -> FD [FDExpr]
nQueens n = do
qs <- news n (1, n)
safeQueens qs
return qs
safeQueens :: [FDExpr] -> FDConstraint
safeQueens [] = return ()
safeQueens (q : qs) = do
safeQueen qs q 1
safeQueens qs
safeQueen :: [FDExpr] -> FDExpr -> FDExpr -> FDConstraint
safeQueen [] _ _ = return ()
safeQueen (q : qs) q0 d0 = do
q0 #= q
abs (q0 - q) #= d0
safeQueen qs q0 (d0 + 1)
• List monad provides backtracking / search / multiple solutions.
• Wrap it in a state monad transformer to keep track of the constraint store.
type FD a = StateT FDState [] a
type FDConstraint = FD ()
-- Run the monad to obtain a list of solutions.
runFD :: FD a -> [a]
runFD fd = evalStateT fd initState
newtype FDVar = FDVar { _unwrapFDVar :: Int } deriving (Ord, Eq)
type VarSupply = FDVar
data Domain
= Set IntSet
| Range Int Int
data VarInfo = VarInfo { _delayedConstraints :: !FDConstraint
, _domain :: !Domain }
type VarMap = Map FDVar VarInfo
data FDState = FDState { _varSupply :: !VarSupply, _varMap :: !VarMap }
initState :: FDState
initState = FDState { _varSupply = FDVar 0, _varMap = Map.empty }
newVar :: ToDomain a => a -> FD FDVar
newVar d = do
v <- use varSupply
varSupply . unwrapFDVar += 1
let vi = initVarInfo & domain .~ toDomain d
varMap . at v ?= vi
return v
newVars :: ToDomain a => Int -> a -> FD [FDVar]
newVars n d = replicateM n (newVar d)
-- Look up the current domain of a variable.
lookup :: FDVar -> FD Domain
lookup x =
use $ varMap . ix x . domain
-- Update the domain of a variable and fire all delayed constraints
-- associated with that variable.
update :: FDVar -> Domain -> FDConstraint
update x i = do
vi <- use $ varMap . ix x
varMap . ix x . domain .= i
vi ^. delayedConstraints
-- Add a new constraint for a variable to the constraint store.
addConstraint :: FDVar -> FDConstraint -> FDConstraint
addConstraint x constraint =
varMap . ix x . delayedConstraints %= (>> constraint)
-- Useful helper function for adding binary constraints between FDVars.
type BinaryConstraint = FDVar -> FDVar -> FDConstraint
addBinaryConstraint :: BinaryConstraint -> BinaryConstraint
addBinaryConstraint f x y = do
let constraint = f x y
constraint
addConstraint x constraint
addConstraint y constraint
-- Constrain two variables to have the same value.
same :: FDVar -> FDVar -> FDConstraint
same = addBinaryConstraint $ x y -> do
xv <- lookup x
yv <- lookup y
let i = xv ‘intersection‘ yv
guard $ not $ Domain.null i
when (i /= xv) $ update x i
when (i /= yv) $ update y i
-- Constrain two variables to have different values.
different :: FDVar -> FDVar -> FDConstraint
different = addBinaryConstraint $ x y -> do
xv <- lookup x
yv <- lookup y
guard $ not (isSingleton xv) || not (isSingleton yv) || xv /= yv
when (isSingleton xv && xv ‘isSubsetOf‘ yv) $
update y (yv ‘difference‘ xv)
when (isSingleton yv && yv ‘isSubsetOf‘ xv) $
update x (xv ‘difference‘ yv)
-- Constrain a list of variables to all have different values.
varsAllDifferent :: [FDVar] -> FDConstraint
varsAllDifferent (x:xs) = do
mapM_ (different x) xs
varsAllDifferent xs
varsAllDifferent _ = return ()
Labelling
Labelling is used to obtain valid solutions for a set of variables. The embedded list
monad allows us to search for and return all possible solutions.
-- Label variables using a depth-first left-to-right search.
varsLabelling :: [FDVar] -> FD [Int]
varsLabelling = mapM label where
label var = do
vals <- lookup var
val <- lift $ elems vals
var ‘hasValue‘ val
return val
We now have enough to solve Sudoku!
sudoku :: [Int] -> [[Int]]
sudoku puzzle = runFD $ do
vars <- newVars 81 (1, 9)
zipWithM_ (x n -> when (n > 0) (x ‘hasValue‘ n)) vars puzzle
mapM_ varsAllDifferent (rows vars)
mapM_ varsAllDifferent (columns vars)
mapM_ varsAllDifferent (boxes vars)
varsLabelling vars
rows, columns, boxes :: [a] -> [[a]]
rows = chunk 9
columns = transpose . rows
boxes = concat . map (map concat . transpose) . chunk 3 . chunk 3 . chunk 3
chunk :: Int -> [a] -> [[a]]
chunk _ [] = []
chunk n xs = ys : chunk n zs where
(ys, zs) = splitAt n xs
Arithemtic expressions
• So far we have seen how to declare contraint variables and define simple equality
constraints between them.
• We also want to be able to write constraints involving simple arithmetic
expressions.
data FDExpr
= Int !Int
| Var !FDVar
| Plus !FDExpr !FDExpr
| Minus !FDExpr !FDExpr
| Times !FDExpr !FDExpr
| Negate !FDExpr
| Abs !FDExpr
| Signum !FDExpr
-- Num instance allows us to use the usual arithmetic operators
-- and integer literals
instance Num FDExpr where
(+) = Plus
(-) = Minus
(*) = Times
negate = Negate
abs = Abs
signum = Signum
fromInteger = Int . fromInteger
-- Define new variables and return as expressions
new :: ToDomain a => a -> FD FDExpr
new d = newVar d <&> Var
news :: ToDomain a => Int -> a -> FD [FDExpr]
news n d = replicateM n $ new d
-- Interpret an FDExpr and return an FDVar representing it
interpret :: FDExpr -> FD FDVar
interpret (Var v) = return v
interpret (Int i) = newVar [i]
interpret (Plus e0 e1) = interpretBinary (+) e0 e1
interpret (Minus e0 e1) = interpretBinary (-) e0 e1
interpret (Times e0 e1) = interpretBinary (*) e0 e1
interpret (Negate e) = interpretUnary negate e
interpret (Abs e) = interpretUnary abs e
interpret (Signum e) = interpretUnary signum e
interpretBinary :: (Int -> Int -> Int) -> FDExpr -> FDExpr -> FD FDVar
interpretBinary op e0 e1 = do
v0 <- interpret e0
v1 <- interpret e1
d0 <- lookup v0
d1 <- lookup v1
v <- newVar [n0 ‘op‘ n1 | n0 <- elems d0, n1 <- elems d1]
let pc = constrainBinary (n n0 n1 -> n == n0 ‘op‘ n1) v v0 v1
nc0 = constrainBinary (n0 n n1 -> n == n0 ‘op‘ n1) v0 v v1
nc1 = constrainBinary (n1 n n0 -> n == n0 ‘op‘ n1) v1 v v0
addConstraint v0 $ pc >> nc1
addConstraint v1 $ pc >> nc0
addConstraint v $ nc0 >> nc1
return v
constrainBinary :: (Int -> Int -> Int -> Bool) -> FDVar -> FDVar -> FDVar -> FDConstraint
constrainBinary pred v v0 v1 = do
d <- lookup v
d0 <- lookup v0
d1 <- lookup v1
let d’ = toDomain [n | n <- elems d, n0 <- elems d0, n1 <- elems d1, pred n n0 n1]
guard $ not $ Domain.null d’
when (d’ /= d) $ update v d’
infix 4 #=
(#=) :: FDExpr -> FDExpr -> FDConstraint
a #= b = do
v0 <- interpret a
v1 <- interpret b
v0 ‘different‘ v1
allDifferent :: [FDExpr] -> FDConstraint
allDifferent = varsAllDifferent <=< mapM interpret
labelling :: [FDExpr] -> FD [Int]
labelling = varsLabelling <=< mapM interpret
Example: n queens in SWI-Prolog and Haskell
n_queens(N, Qs) :-
length(Qs, N),
Qs ins 1..N,
safe_queens(Qs).
safe_queens([]).
safe_queens([Q|Qs]) :-
safe_queen(Qs, Q, 1),
safe_queens(Qs).
safe_queen([], _, _).
safe_queen([Q|Qs], Q0, D0) :-
Q0 #= Q,
abs(Q0 - Q) #= D0,
D1 #= D0 + 1,
safe_queen(Qs, Q0, D1).
nQueens :: Int -> FD [FDExpr]
nQueens n = do
qs <- news n (1, n)
safeQueens qs
return qs
safeQueens :: [FDExpr] -> FDConstraint
safeQueens [] = return ()
safeQueens (q : qs) = do
safeQueen qs q 1
safeQueens qs
safeQueen :: [FDExpr] -> FDExpr -> FDExpr -> FDConstraint
safeQueen [] _ _ = return ()
safeQueen (q : qs) q0 d0 = do
q0 #= q
abs (q0 - q) #= d0
safeQueen qs q0 (d0 + 1)
SEND
+ MORE
-------
MONEY
sendMoreMoney = runFD $ do
vars@[s, e, n, d, m, o, r, y] <- news 8 (0, 9)
s #= 0
m #= 0
allDifferent vars
1000 * s + 100 * e + 10 * n + d
+ 1000 * m + 100 * o + 10 * r + e
#== 10000 * m + 1000 * o + 100 * n + 10 * e + y
labelling vars
Table of Contents
1 Constraint programming
2 Constraint logic programming
3 Finite domain constraints
4 Constraint programming in Haskell
Basic equality and inequality
Arithmetic expressions
5 Conclusion
Consclusion
• Haskell can do constraint logic programming – all you need is monads.
• Advantages of Haskell
• Awesomeness of Haskell.
• Type safety.
• Leverage libraries, such as monad combinators, in a very natural way.
• Disadvantages
• Not full Prolog, e.g. missing unification between terms, multi-moded predicates.
• Some Prolog implementations have very powerful and efficient built-in solvers, which
Haskell can’t use.
Github repository: https://github.com/dmoverton/finite-domain

Weitere ähnliche Inhalte

Was ist angesagt?

Data Structures in javaScript 2015
Data Structures in javaScript 2015Data Structures in javaScript 2015
Data Structures in javaScript 2015Nir Kaufman
 
Bellman ford algorithm
Bellman ford algorithmBellman ford algorithm
Bellman ford algorithmRuchika Sinha
 
Knapsack Problem (DP & GREEDY)
Knapsack Problem (DP & GREEDY)Knapsack Problem (DP & GREEDY)
Knapsack Problem (DP & GREEDY)Ridhima Chowdhury
 
Kotlin InDepth Tutorial for beginners 2022
Kotlin InDepth Tutorial for beginners 2022Kotlin InDepth Tutorial for beginners 2022
Kotlin InDepth Tutorial for beginners 2022Simplilearn
 
Regular Expressions Cheat Sheet
Regular Expressions Cheat SheetRegular Expressions Cheat Sheet
Regular Expressions Cheat SheetAkash Bisariya
 
One Step Ahead of Cheaters -- Instrumenting Android Emulators
One Step Ahead of Cheaters -- Instrumenting Android EmulatorsOne Step Ahead of Cheaters -- Instrumenting Android Emulators
One Step Ahead of Cheaters -- Instrumenting Android EmulatorsPriyanka Aash
 
Floyd Warshall Algorithm
Floyd Warshall Algorithm Floyd Warshall Algorithm
Floyd Warshall Algorithm Imamul Kadir
 
Sum and Product Types - The Fruit Salad & Fruit Snack Example - From F# to Ha...
Sum and Product Types -The Fruit Salad & Fruit Snack Example - From F# to Ha...Sum and Product Types -The Fruit Salad & Fruit Snack Example - From F# to Ha...
Sum and Product Types - The Fruit Salad & Fruit Snack Example - From F# to Ha...Philip Schwarz
 
Ch3 4 regular expression and grammar
Ch3 4 regular expression and grammarCh3 4 regular expression and grammar
Ch3 4 regular expression and grammarmeresie tesfay
 
Rabin Carp String Matching algorithm
Rabin Carp String Matching  algorithmRabin Carp String Matching  algorithm
Rabin Carp String Matching algorithmsabiya sabiya
 
Monad Laws Must be Checked
Monad Laws Must be CheckedMonad Laws Must be Checked
Monad Laws Must be CheckedPhilip Schwarz
 
The Functional Programming Triad of Map, Filter and Fold
The Functional Programming Triad of Map, Filter and FoldThe Functional Programming Triad of Map, Filter and Fold
The Functional Programming Triad of Map, Filter and FoldPhilip Schwarz
 
Blazing Fast, Pure Effects without Monads — LambdaConf 2018
Blazing Fast, Pure Effects without Monads — LambdaConf 2018Blazing Fast, Pure Effects without Monads — LambdaConf 2018
Blazing Fast, Pure Effects without Monads — LambdaConf 2018John De Goes
 

Was ist angesagt? (20)

Data Structures in javaScript 2015
Data Structures in javaScript 2015Data Structures in javaScript 2015
Data Structures in javaScript 2015
 
Skip List
Skip ListSkip List
Skip List
 
Bellman ford algorithm
Bellman ford algorithmBellman ford algorithm
Bellman ford algorithm
 
Knapsack Problem (DP & GREEDY)
Knapsack Problem (DP & GREEDY)Knapsack Problem (DP & GREEDY)
Knapsack Problem (DP & GREEDY)
 
Kotlin InDepth Tutorial for beginners 2022
Kotlin InDepth Tutorial for beginners 2022Kotlin InDepth Tutorial for beginners 2022
Kotlin InDepth Tutorial for beginners 2022
 
Regular Expressions Cheat Sheet
Regular Expressions Cheat SheetRegular Expressions Cheat Sheet
Regular Expressions Cheat Sheet
 
One Step Ahead of Cheaters -- Instrumenting Android Emulators
One Step Ahead of Cheaters -- Instrumenting Android EmulatorsOne Step Ahead of Cheaters -- Instrumenting Android Emulators
One Step Ahead of Cheaters -- Instrumenting Android Emulators
 
Application of dfs
Application of dfsApplication of dfs
Application of dfs
 
Floyd Warshall Algorithm
Floyd Warshall Algorithm Floyd Warshall Algorithm
Floyd Warshall Algorithm
 
Sum and Product Types - The Fruit Salad & Fruit Snack Example - From F# to Ha...
Sum and Product Types -The Fruit Salad & Fruit Snack Example - From F# to Ha...Sum and Product Types -The Fruit Salad & Fruit Snack Example - From F# to Ha...
Sum and Product Types - The Fruit Salad & Fruit Snack Example - From F# to Ha...
 
The Floyd–Warshall algorithm
The Floyd–Warshall algorithmThe Floyd–Warshall algorithm
The Floyd–Warshall algorithm
 
Recursion
RecursionRecursion
Recursion
 
Rabin Karp ppt
Rabin Karp pptRabin Karp ppt
Rabin Karp ppt
 
Ch3 4 regular expression and grammar
Ch3 4 regular expression and grammarCh3 4 regular expression and grammar
Ch3 4 regular expression and grammar
 
Kotlin arrays
Kotlin arraysKotlin arrays
Kotlin arrays
 
LCS Presentation
LCS PresentationLCS Presentation
LCS Presentation
 
Rabin Carp String Matching algorithm
Rabin Carp String Matching  algorithmRabin Carp String Matching  algorithm
Rabin Carp String Matching algorithm
 
Monad Laws Must be Checked
Monad Laws Must be CheckedMonad Laws Must be Checked
Monad Laws Must be Checked
 
The Functional Programming Triad of Map, Filter and Fold
The Functional Programming Triad of Map, Filter and FoldThe Functional Programming Triad of Map, Filter and Fold
The Functional Programming Triad of Map, Filter and Fold
 
Blazing Fast, Pure Effects without Monads — LambdaConf 2018
Blazing Fast, Pure Effects without Monads — LambdaConf 2018Blazing Fast, Pure Effects without Monads — LambdaConf 2018
Blazing Fast, Pure Effects without Monads — LambdaConf 2018
 

Andere mochten auch

Yampa AFRP Introduction
Yampa AFRP IntroductionYampa AFRP Introduction
Yampa AFRP IntroductionChengHui Weng
 
Re-engineering the Operating Room Using Variability Methodology to Improve He...
Re-engineering the Operating Room Using Variability Methodology to Improve He...Re-engineering the Operating Room Using Variability Methodology to Improve He...
Re-engineering the Operating Room Using Variability Methodology to Improve He...C Daniel Smith
 
Functional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedFunctional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedSusan Potter
 
Catch a spider monkey
Catch a spider monkeyCatch a spider monkey
Catch a spider monkeyChengHui Weng
 
Domain Driven Design
Domain Driven DesignDomain Driven Design
Domain Driven DesignRyan Riley
 
The other side of functional programming: Haskell for Erlang people
The other side of functional programming: Haskell for Erlang peopleThe other side of functional programming: Haskell for Erlang people
The other side of functional programming: Haskell for Erlang peopleBryan O'Sullivan
 
The Data Dichotomy- Rethinking the Way We Treat Data and Services
The Data Dichotomy- Rethinking the Way We Treat Data and ServicesThe Data Dichotomy- Rethinking the Way We Treat Data and Services
The Data Dichotomy- Rethinking the Way We Treat Data and Servicesconfluent
 
Steps to apply for Passport Services
Steps to apply for Passport ServicesSteps to apply for Passport Services
Steps to apply for Passport Servicespassportindia
 

Andere mochten auch (11)

Comonads in Haskell
Comonads in HaskellComonads in Haskell
Comonads in Haskell
 
Yampa AFRP Introduction
Yampa AFRP IntroductionYampa AFRP Introduction
Yampa AFRP Introduction
 
Re-engineering the Operating Room Using Variability Methodology to Improve He...
Re-engineering the Operating Room Using Variability Methodology to Improve He...Re-engineering the Operating Room Using Variability Methodology to Improve He...
Re-engineering the Operating Room Using Variability Methodology to Improve He...
 
Functional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedFunctional Algebra: Monoids Applied
Functional Algebra: Monoids Applied
 
Zippers
ZippersZippers
Zippers
 
Catch a spider monkey
Catch a spider monkeyCatch a spider monkey
Catch a spider monkey
 
Domain Driven Design
Domain Driven DesignDomain Driven Design
Domain Driven Design
 
The other side of functional programming: Haskell for Erlang people
The other side of functional programming: Haskell for Erlang peopleThe other side of functional programming: Haskell for Erlang people
The other side of functional programming: Haskell for Erlang people
 
The Data Dichotomy- Rethinking the Way We Treat Data and Services
The Data Dichotomy- Rethinking the Way We Treat Data and ServicesThe Data Dichotomy- Rethinking the Way We Treat Data and Services
The Data Dichotomy- Rethinking the Way We Treat Data and Services
 
dmo-phd-thesis
dmo-phd-thesisdmo-phd-thesis
dmo-phd-thesis
 
Steps to apply for Passport Services
Steps to apply for Passport ServicesSteps to apply for Passport Services
Steps to apply for Passport Services
 

Ähnlich wie Constraint Programming in Haskell

RedisConf18 - CRDTs and Redis - From sequential to concurrent executions
RedisConf18 - CRDTs and Redis - From sequential to concurrent executionsRedisConf18 - CRDTs and Redis - From sequential to concurrent executions
RedisConf18 - CRDTs and Redis - From sequential to concurrent executionsRedis Labs
 
Building High-Performance Language Implementations With Low Effort
Building High-Performance Language Implementations With Low EffortBuilding High-Performance Language Implementations With Low Effort
Building High-Performance Language Implementations With Low EffortStefan Marr
 
re:mobidyc the overview
re:mobidyc the overviewre:mobidyc the overview
re:mobidyc the overviewESUG
 
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docx
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docxDivide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docx
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docxjacksnathalie
 
Flying Futures at the same sky can make the sun rise at midnight
Flying Futures at the same sky can make the sun rise at midnightFlying Futures at the same sky can make the sun rise at midnight
Flying Futures at the same sky can make the sun rise at midnightWiem Zine Elabidine
 
Matlab-free course by Mohd Esa
Matlab-free course by Mohd EsaMatlab-free course by Mohd Esa
Matlab-free course by Mohd EsaMohd Esa
 
Font classification with 5 deep learning models using tensor flow
Font classification with 5 deep learning models using tensor flowFont classification with 5 deep learning models using tensor flow
Font classification with 5 deep learning models using tensor flowDevatanu Banerjee
 
Basic R Data Manipulation
Basic R Data ManipulationBasic R Data Manipulation
Basic R Data ManipulationChu An
 
Introduction to R programming
Introduction to R programmingIntroduction to R programming
Introduction to R programmingAlberto Labarga
 
Itroroduction to R language
Itroroduction to R languageItroroduction to R language
Itroroduction to R languagechhabria-nitesh
 
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...confluent
 
Introduction to matlab lecture 3 of 4
Introduction to matlab lecture 3 of 4Introduction to matlab lecture 3 of 4
Introduction to matlab lecture 3 of 4Randa Elanwar
 
From Java to Scala - advantages and possible risks
From Java to Scala - advantages and possible risksFrom Java to Scala - advantages and possible risks
From Java to Scala - advantages and possible risksSeniorDevOnly
 

Ähnlich wie Constraint Programming in Haskell (20)

RedisConf18 - CRDTs and Redis - From sequential to concurrent executions
RedisConf18 - CRDTs and Redis - From sequential to concurrent executionsRedisConf18 - CRDTs and Redis - From sequential to concurrent executions
RedisConf18 - CRDTs and Redis - From sequential to concurrent executions
 
Building High-Performance Language Implementations With Low Effort
Building High-Performance Language Implementations With Low EffortBuilding High-Performance Language Implementations With Low Effort
Building High-Performance Language Implementations With Low Effort
 
re:mobidyc the overview
re:mobidyc the overviewre:mobidyc the overview
re:mobidyc the overview
 
Strategy Synthesis for Data-Aware Dynamic Systems with Multiple Actors
Strategy Synthesis for Data-Aware Dynamic Systems with Multiple ActorsStrategy Synthesis for Data-Aware Dynamic Systems with Multiple Actors
Strategy Synthesis for Data-Aware Dynamic Systems with Multiple Actors
 
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docx
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docxDivide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docx
Divide-and-Conquer & Dynamic ProgrammingDivide-and-Conqu.docx
 
Reactive x
Reactive xReactive x
Reactive x
 
Statistics lab 1
Statistics lab 1Statistics lab 1
Statistics lab 1
 
Flying Futures at the same sky can make the sun rise at midnight
Flying Futures at the same sky can make the sun rise at midnightFlying Futures at the same sky can make the sun rise at midnight
Flying Futures at the same sky can make the sun rise at midnight
 
Introduction to R
Introduction to RIntroduction to R
Introduction to R
 
Matlab-free course by Mohd Esa
Matlab-free course by Mohd EsaMatlab-free course by Mohd Esa
Matlab-free course by Mohd Esa
 
Font classification with 5 deep learning models using tensor flow
Font classification with 5 deep learning models using tensor flowFont classification with 5 deep learning models using tensor flow
Font classification with 5 deep learning models using tensor flow
 
Basic R Data Manipulation
Basic R Data ManipulationBasic R Data Manipulation
Basic R Data Manipulation
 
Lecture 3
Lecture 3Lecture 3
Lecture 3
 
Introduction to R programming
Introduction to R programmingIntroduction to R programming
Introduction to R programming
 
Spark workshop
Spark workshopSpark workshop
Spark workshop
 
Seminar PSU 10.10.2014 mme
Seminar PSU 10.10.2014 mmeSeminar PSU 10.10.2014 mme
Seminar PSU 10.10.2014 mme
 
Itroroduction to R language
Itroroduction to R languageItroroduction to R language
Itroroduction to R language
 
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...
Data-Oriented Programming with Clojure and Jackdaw (Charles Reese, Funding Ci...
 
Introduction to matlab lecture 3 of 4
Introduction to matlab lecture 3 of 4Introduction to matlab lecture 3 of 4
Introduction to matlab lecture 3 of 4
 
From Java to Scala - advantages and possible risks
From Java to Scala - advantages and possible risksFrom Java to Scala - advantages and possible risks
From Java to Scala - advantages and possible risks
 

Kürzlich hochgeladen

Xen Safety Embedded OSS Summit April 2024 v4.pdf
Xen Safety Embedded OSS Summit April 2024 v4.pdfXen Safety Embedded OSS Summit April 2024 v4.pdf
Xen Safety Embedded OSS Summit April 2024 v4.pdfStefano Stabellini
 
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...OnePlan Solutions
 
Odoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 EnterpriseOdoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 Enterprisepreethippts
 
VK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web DevelopmentVK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web Developmentvyaparkranti
 
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...Angel Borroy López
 
Precise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalPrecise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalLionel Briand
 
Recruitment Management Software Benefits (Infographic)
Recruitment Management Software Benefits (Infographic)Recruitment Management Software Benefits (Infographic)
Recruitment Management Software Benefits (Infographic)Hr365.us smith
 
Cloud Data Center Network Construction - IEEE
Cloud Data Center Network Construction - IEEECloud Data Center Network Construction - IEEE
Cloud Data Center Network Construction - IEEEVICTOR MAESTRE RAMIREZ
 
MYjobs Presentation Django-based project
MYjobs Presentation Django-based projectMYjobs Presentation Django-based project
MYjobs Presentation Django-based projectAnoyGreter
 
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdf
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdfInnovate and Collaborate- Harnessing the Power of Open Source Software.pdf
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdfYashikaSharma391629
 
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Natan Silnitsky
 
Powering Real-Time Decisions with Continuous Data Streams
Powering Real-Time Decisions with Continuous Data StreamsPowering Real-Time Decisions with Continuous Data Streams
Powering Real-Time Decisions with Continuous Data StreamsSafe Software
 
Implementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureImplementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureDinusha Kumarasiri
 
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024StefanoLambiase
 
Unveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesUnveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesŁukasz Chruściel
 
Comparing Linux OS Image Update Models - EOSS 2024.pdf
Comparing Linux OS Image Update Models - EOSS 2024.pdfComparing Linux OS Image Update Models - EOSS 2024.pdf
Comparing Linux OS Image Update Models - EOSS 2024.pdfDrew Moseley
 
Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Velvetech LLC
 
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...OnePlan Solutions
 
Salesforce Implementation Services PPT By ABSYZ
Salesforce Implementation Services PPT By ABSYZSalesforce Implementation Services PPT By ABSYZ
Salesforce Implementation Services PPT By ABSYZABSYZ Inc
 
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...confluent
 

Kürzlich hochgeladen (20)

Xen Safety Embedded OSS Summit April 2024 v4.pdf
Xen Safety Embedded OSS Summit April 2024 v4.pdfXen Safety Embedded OSS Summit April 2024 v4.pdf
Xen Safety Embedded OSS Summit April 2024 v4.pdf
 
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...
Tech Tuesday - Mastering Time Management Unlock the Power of OnePlan's Timesh...
 
Odoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 EnterpriseOdoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 Enterprise
 
VK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web DevelopmentVK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web Development
 
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...
Alfresco TTL#157 - Troubleshooting Made Easy: Deciphering Alfresco mTLS Confi...
 
Precise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalPrecise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive Goal
 
Recruitment Management Software Benefits (Infographic)
Recruitment Management Software Benefits (Infographic)Recruitment Management Software Benefits (Infographic)
Recruitment Management Software Benefits (Infographic)
 
Cloud Data Center Network Construction - IEEE
Cloud Data Center Network Construction - IEEECloud Data Center Network Construction - IEEE
Cloud Data Center Network Construction - IEEE
 
MYjobs Presentation Django-based project
MYjobs Presentation Django-based projectMYjobs Presentation Django-based project
MYjobs Presentation Django-based project
 
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdf
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdfInnovate and Collaborate- Harnessing the Power of Open Source Software.pdf
Innovate and Collaborate- Harnessing the Power of Open Source Software.pdf
 
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
 
Powering Real-Time Decisions with Continuous Data Streams
Powering Real-Time Decisions with Continuous Data StreamsPowering Real-Time Decisions with Continuous Data Streams
Powering Real-Time Decisions with Continuous Data Streams
 
Implementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureImplementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with Azure
 
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024
Dealing with Cultural Dispersion — Stefano Lambiase — ICSE-SEIS 2024
 
Unveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesUnveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New Features
 
Comparing Linux OS Image Update Models - EOSS 2024.pdf
Comparing Linux OS Image Update Models - EOSS 2024.pdfComparing Linux OS Image Update Models - EOSS 2024.pdf
Comparing Linux OS Image Update Models - EOSS 2024.pdf
 
Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...
 
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...
Maximizing Efficiency and Profitability with OnePlan’s Professional Service A...
 
Salesforce Implementation Services PPT By ABSYZ
Salesforce Implementation Services PPT By ABSYZSalesforce Implementation Services PPT By ABSYZ
Salesforce Implementation Services PPT By ABSYZ
 
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...
Catch the Wave: SAP Event-Driven and Data Streaming for the Intelligence Ente...
 

Constraint Programming in Haskell

  • 1. Constraint Programming in Haskell Melbourne Haskell Users Group David Overton 29 October 2015
  • 2. Table of Contents 1 Constraint programming 2 Constraint logic programming 3 Finite domain constraints 4 Constraint programming in Haskell Basic equality and inequality Arithmetic expressions 5 Conclusion
  • 3. Constraint programming Constraint programming is a declarative programming paradigm for solving constraint satisfaction problems. • A set of constraint variables over a domain, e.g. Booleans, integers, reals, finite domain. • A set of constraints between those variables. • A solver to find solutions to the constraints, i.e. assignments of variables to values in the domain such that all constraints are satisfied. Applications: planning, scheduling, resource allocation, computer graphics, digital circuit design, programming language analysis, . . .
  • 4. Table of Contents 1 Constraint programming 2 Constraint logic programming 3 Finite domain constraints 4 Constraint programming in Haskell Basic equality and inequality Arithmetic expressions 5 Conclusion
  • 5. Constraint logic programming • Constraint programming and logic programming work well together. • Many Prolog implementations have built in constraint solvers. • Basic idea: • add constraints to the constraint store • constraint solver works behind the scenes to propagate constraints • use Prolog’s backtracking search mechanism to generate solutions • Advantages over pure logic programming: • “constrain-and-generate” rather than “generate-and-test” • constraint solver can greatly reduce the search space required compared to Prolog’s built-in depth-first-search • much more powerful than relying on just unification and backtracking
  • 6. Table of Contents 1 Constraint programming 2 Constraint logic programming 3 Finite domain constraints 4 Constraint programming in Haskell Basic equality and inequality Arithmetic expressions 5 Conclusion
  • 7. Finite domain constraints • One of the most widely used varieties of constraint solver. • Variables range over a finite domain of integers. • Simple equality and inequality constraints: =, =, <, >, ≤, ≥ • Also simple arithmetic expressions: +, −, ×, abs
  • 8. Arc consistency Solver uses an arc consistency algorithm, e.g. AC-3 • Constraint store holds the set of constraints to be checked. • For each constraint, the domains of the variables involved are checked to ensure they are consistent with the contraint. • Any values in the domains that break consistency are removed. • If the domain of a variable changes then all other constraints involving that variable are rechecked. Example x ∈ {1, 2, 3} ∧ y ∈ {1, 2, 3} add constraint x < y ⇒ x ∈ {1, 2} ∧ y ∈ {2, 3} add constraint y = 2 ⇒ x ∈ {1} ∧ y ∈ {2}
  • 9. Example: n queens in SWI-Prolog n_queens(N, Qs) :- length(Qs, N), Qs ins 1..N, safe_queens(Qs). safe_queens([]). safe_queens([Q|Qs]) :- safe_queen(Qs, Q, 1), safe_queens(Qs). safe_queen([], _, _). safe_queen([Q|Qs], Q0, D0) :- Q0 #= Q, abs(Q0 - Q) #= D0, D1 #= D0 + 1, safe_queen(Qs, Q0, D1).
  • 10. Table of Contents 1 Constraint programming 2 Constraint logic programming 3 Finite domain constraints 4 Constraint programming in Haskell Basic equality and inequality Arithmetic expressions 5 Conclusion
  • 11. Constraint programming in Haskell How can we do something similar in Haskell? Use a monad!
  • 12. Example: n queens in SWI-Prolog and Haskell n_queens(N, Qs) :- length(Qs, N), Qs ins 1..N, safe_queens(Qs). safe_queens([]). safe_queens([Q|Qs]) :- safe_queen(Qs, Q, 1), safe_queens(Qs). safe_queen([], _, _). safe_queen([Q|Qs], Q0, D0) :- Q0 #= Q, abs(Q0 - Q) #= D0, D1 #= D0 + 1, safe_queen(Qs, Q0, D1). nQueens :: Int -> FD [FDExpr] nQueens n = do qs <- news n (1, n) safeQueens qs return qs safeQueens :: [FDExpr] -> FDConstraint safeQueens [] = return () safeQueens (q : qs) = do safeQueen qs q 1 safeQueens qs safeQueen :: [FDExpr] -> FDExpr -> FDExpr -> FDConstraint safeQueen [] _ _ = return () safeQueen (q : qs) q0 d0 = do q0 #= q abs (q0 - q) #= d0 safeQueen qs q0 (d0 + 1)
  • 13. • List monad provides backtracking / search / multiple solutions. • Wrap it in a state monad transformer to keep track of the constraint store. type FD a = StateT FDState [] a type FDConstraint = FD () -- Run the monad to obtain a list of solutions. runFD :: FD a -> [a] runFD fd = evalStateT fd initState
  • 14. newtype FDVar = FDVar { _unwrapFDVar :: Int } deriving (Ord, Eq) type VarSupply = FDVar data Domain = Set IntSet | Range Int Int data VarInfo = VarInfo { _delayedConstraints :: !FDConstraint , _domain :: !Domain } type VarMap = Map FDVar VarInfo data FDState = FDState { _varSupply :: !VarSupply, _varMap :: !VarMap } initState :: FDState initState = FDState { _varSupply = FDVar 0, _varMap = Map.empty }
  • 15. newVar :: ToDomain a => a -> FD FDVar newVar d = do v <- use varSupply varSupply . unwrapFDVar += 1 let vi = initVarInfo & domain .~ toDomain d varMap . at v ?= vi return v newVars :: ToDomain a => Int -> a -> FD [FDVar] newVars n d = replicateM n (newVar d)
  • 16. -- Look up the current domain of a variable. lookup :: FDVar -> FD Domain lookup x = use $ varMap . ix x . domain -- Update the domain of a variable and fire all delayed constraints -- associated with that variable. update :: FDVar -> Domain -> FDConstraint update x i = do vi <- use $ varMap . ix x varMap . ix x . domain .= i vi ^. delayedConstraints -- Add a new constraint for a variable to the constraint store. addConstraint :: FDVar -> FDConstraint -> FDConstraint addConstraint x constraint = varMap . ix x . delayedConstraints %= (>> constraint)
  • 17. -- Useful helper function for adding binary constraints between FDVars. type BinaryConstraint = FDVar -> FDVar -> FDConstraint addBinaryConstraint :: BinaryConstraint -> BinaryConstraint addBinaryConstraint f x y = do let constraint = f x y constraint addConstraint x constraint addConstraint y constraint -- Constrain two variables to have the same value. same :: FDVar -> FDVar -> FDConstraint same = addBinaryConstraint $ x y -> do xv <- lookup x yv <- lookup y let i = xv ‘intersection‘ yv guard $ not $ Domain.null i when (i /= xv) $ update x i when (i /= yv) $ update y i
  • 18. -- Constrain two variables to have different values. different :: FDVar -> FDVar -> FDConstraint different = addBinaryConstraint $ x y -> do xv <- lookup x yv <- lookup y guard $ not (isSingleton xv) || not (isSingleton yv) || xv /= yv when (isSingleton xv && xv ‘isSubsetOf‘ yv) $ update y (yv ‘difference‘ xv) when (isSingleton yv && yv ‘isSubsetOf‘ xv) $ update x (xv ‘difference‘ yv) -- Constrain a list of variables to all have different values. varsAllDifferent :: [FDVar] -> FDConstraint varsAllDifferent (x:xs) = do mapM_ (different x) xs varsAllDifferent xs varsAllDifferent _ = return ()
  • 19. Labelling Labelling is used to obtain valid solutions for a set of variables. The embedded list monad allows us to search for and return all possible solutions. -- Label variables using a depth-first left-to-right search. varsLabelling :: [FDVar] -> FD [Int] varsLabelling = mapM label where label var = do vals <- lookup var val <- lift $ elems vals var ‘hasValue‘ val return val
  • 20. We now have enough to solve Sudoku! sudoku :: [Int] -> [[Int]] sudoku puzzle = runFD $ do vars <- newVars 81 (1, 9) zipWithM_ (x n -> when (n > 0) (x ‘hasValue‘ n)) vars puzzle mapM_ varsAllDifferent (rows vars) mapM_ varsAllDifferent (columns vars) mapM_ varsAllDifferent (boxes vars) varsLabelling vars rows, columns, boxes :: [a] -> [[a]] rows = chunk 9 columns = transpose . rows boxes = concat . map (map concat . transpose) . chunk 3 . chunk 3 . chunk 3 chunk :: Int -> [a] -> [[a]] chunk _ [] = [] chunk n xs = ys : chunk n zs where (ys, zs) = splitAt n xs
  • 21. Arithemtic expressions • So far we have seen how to declare contraint variables and define simple equality constraints between them. • We also want to be able to write constraints involving simple arithmetic expressions.
  • 22. data FDExpr = Int !Int | Var !FDVar | Plus !FDExpr !FDExpr | Minus !FDExpr !FDExpr | Times !FDExpr !FDExpr | Negate !FDExpr | Abs !FDExpr | Signum !FDExpr -- Num instance allows us to use the usual arithmetic operators -- and integer literals instance Num FDExpr where (+) = Plus (-) = Minus (*) = Times negate = Negate abs = Abs signum = Signum fromInteger = Int . fromInteger
  • 23. -- Define new variables and return as expressions new :: ToDomain a => a -> FD FDExpr new d = newVar d <&> Var news :: ToDomain a => Int -> a -> FD [FDExpr] news n d = replicateM n $ new d -- Interpret an FDExpr and return an FDVar representing it interpret :: FDExpr -> FD FDVar interpret (Var v) = return v interpret (Int i) = newVar [i] interpret (Plus e0 e1) = interpretBinary (+) e0 e1 interpret (Minus e0 e1) = interpretBinary (-) e0 e1 interpret (Times e0 e1) = interpretBinary (*) e0 e1 interpret (Negate e) = interpretUnary negate e interpret (Abs e) = interpretUnary abs e interpret (Signum e) = interpretUnary signum e
  • 24. interpretBinary :: (Int -> Int -> Int) -> FDExpr -> FDExpr -> FD FDVar interpretBinary op e0 e1 = do v0 <- interpret e0 v1 <- interpret e1 d0 <- lookup v0 d1 <- lookup v1 v <- newVar [n0 ‘op‘ n1 | n0 <- elems d0, n1 <- elems d1] let pc = constrainBinary (n n0 n1 -> n == n0 ‘op‘ n1) v v0 v1 nc0 = constrainBinary (n0 n n1 -> n == n0 ‘op‘ n1) v0 v v1 nc1 = constrainBinary (n1 n n0 -> n == n0 ‘op‘ n1) v1 v v0 addConstraint v0 $ pc >> nc1 addConstraint v1 $ pc >> nc0 addConstraint v $ nc0 >> nc1 return v constrainBinary :: (Int -> Int -> Int -> Bool) -> FDVar -> FDVar -> FDVar -> FDConstraint constrainBinary pred v v0 v1 = do d <- lookup v d0 <- lookup v0 d1 <- lookup v1 let d’ = toDomain [n | n <- elems d, n0 <- elems d0, n1 <- elems d1, pred n n0 n1] guard $ not $ Domain.null d’ when (d’ /= d) $ update v d’
  • 25. infix 4 #= (#=) :: FDExpr -> FDExpr -> FDConstraint a #= b = do v0 <- interpret a v1 <- interpret b v0 ‘different‘ v1 allDifferent :: [FDExpr] -> FDConstraint allDifferent = varsAllDifferent <=< mapM interpret labelling :: [FDExpr] -> FD [Int] labelling = varsLabelling <=< mapM interpret
  • 26. Example: n queens in SWI-Prolog and Haskell n_queens(N, Qs) :- length(Qs, N), Qs ins 1..N, safe_queens(Qs). safe_queens([]). safe_queens([Q|Qs]) :- safe_queen(Qs, Q, 1), safe_queens(Qs). safe_queen([], _, _). safe_queen([Q|Qs], Q0, D0) :- Q0 #= Q, abs(Q0 - Q) #= D0, D1 #= D0 + 1, safe_queen(Qs, Q0, D1). nQueens :: Int -> FD [FDExpr] nQueens n = do qs <- news n (1, n) safeQueens qs return qs safeQueens :: [FDExpr] -> FDConstraint safeQueens [] = return () safeQueens (q : qs) = do safeQueen qs q 1 safeQueens qs safeQueen :: [FDExpr] -> FDExpr -> FDExpr -> FDConstraint safeQueen [] _ _ = return () safeQueen (q : qs) q0 d0 = do q0 #= q abs (q0 - q) #= d0 safeQueen qs q0 (d0 + 1)
  • 27. SEND + MORE ------- MONEY sendMoreMoney = runFD $ do vars@[s, e, n, d, m, o, r, y] <- news 8 (0, 9) s #= 0 m #= 0 allDifferent vars 1000 * s + 100 * e + 10 * n + d + 1000 * m + 100 * o + 10 * r + e #== 10000 * m + 1000 * o + 100 * n + 10 * e + y labelling vars
  • 28. Table of Contents 1 Constraint programming 2 Constraint logic programming 3 Finite domain constraints 4 Constraint programming in Haskell Basic equality and inequality Arithmetic expressions 5 Conclusion
  • 29. Consclusion • Haskell can do constraint logic programming – all you need is monads. • Advantages of Haskell • Awesomeness of Haskell. • Type safety. • Leverage libraries, such as monad combinators, in a very natural way. • Disadvantages • Not full Prolog, e.g. missing unification between terms, multi-moded predicates. • Some Prolog implementations have very powerful and efficient built-in solvers, which Haskell can’t use. Github repository: https://github.com/dmoverton/finite-domain