SlideShare une entreprise Scribd logo
1  sur  29
Télécharger pour lire hors ligne
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

Contenu connexe

Tendances

Partial differentiation
Partial differentiationPartial differentiation
Partial differentiationTanuj Parikh
 
A note on word embedding
A note on word embeddingA note on word embedding
A note on word embeddingKhang Pham
 
2 lectures 16 17-informed search algorithms ch 4.3
2 lectures 16 17-informed search algorithms ch 4.32 lectures 16 17-informed search algorithms ch 4.3
2 lectures 16 17-informed search algorithms ch 4.3Ravi Balout
 
Natural Language processing Parts of speech tagging, its classes, and how to ...
Natural Language processing Parts of speech tagging, its classes, and how to ...Natural Language processing Parts of speech tagging, its classes, and how to ...
Natural Language processing Parts of speech tagging, its classes, and how to ...Rajnish Raj
 
Matroid Basics
Matroid BasicsMatroid Basics
Matroid BasicsASPAK2014
 
word2vec, LDA, and introducing a new hybrid algorithm: lda2vec
word2vec, LDA, and introducing a new hybrid algorithm: lda2vecword2vec, LDA, and introducing a new hybrid algorithm: lda2vec
word2vec, LDA, and introducing a new hybrid algorithm: lda2vec👋 Christopher Moody
 
Inverse Function.pptx
Inverse Function.pptxInverse Function.pptx
Inverse Function.pptxSerGeo5
 
4.5 continuous functions and differentiable functions
4.5 continuous functions and differentiable functions4.5 continuous functions and differentiable functions
4.5 continuous functions and differentiable functionsmath265
 
Langrange Interpolation Polynomials
Langrange Interpolation PolynomialsLangrange Interpolation Polynomials
Langrange Interpolation PolynomialsSohaib H. Khan
 
Word representations in vector space
Word representations in vector spaceWord representations in vector space
Word representations in vector spaceAbdullah Khan Zehady
 
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchal
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchalppt on Vector spaces (VCLA) by dhrumil patel and harshid panchal
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchalharshid panchal
 
Flow Network Talk
Flow Network TalkFlow Network Talk
Flow Network TalkImane Haf
 
Partial Differentiation
Partial DifferentiationPartial Differentiation
Partial DifferentiationDeep Dalsania
 

Tendances (20)

Matrix calculus
Matrix calculusMatrix calculus
Matrix calculus
 
FM calculus
FM calculusFM calculus
FM calculus
 
Partial differentiation
Partial differentiationPartial differentiation
Partial differentiation
 
A note on word embedding
A note on word embeddingA note on word embedding
A note on word embedding
 
Greedy algorithm
Greedy algorithmGreedy algorithm
Greedy algorithm
 
LinearAlgebra.ppt
LinearAlgebra.pptLinearAlgebra.ppt
LinearAlgebra.ppt
 
2 lectures 16 17-informed search algorithms ch 4.3
2 lectures 16 17-informed search algorithms ch 4.32 lectures 16 17-informed search algorithms ch 4.3
2 lectures 16 17-informed search algorithms ch 4.3
 
Natural Language processing Parts of speech tagging, its classes, and how to ...
Natural Language processing Parts of speech tagging, its classes, and how to ...Natural Language processing Parts of speech tagging, its classes, and how to ...
Natural Language processing Parts of speech tagging, its classes, and how to ...
 
Matroid Basics
Matroid BasicsMatroid Basics
Matroid Basics
 
word2vec, LDA, and introducing a new hybrid algorithm: lda2vec
word2vec, LDA, and introducing a new hybrid algorithm: lda2vecword2vec, LDA, and introducing a new hybrid algorithm: lda2vec
word2vec, LDA, and introducing a new hybrid algorithm: lda2vec
 
Inverse Function.pptx
Inverse Function.pptxInverse Function.pptx
Inverse Function.pptx
 
4.5 continuous functions and differentiable functions
4.5 continuous functions and differentiable functions4.5 continuous functions and differentiable functions
4.5 continuous functions and differentiable functions
 
Langrange Interpolation Polynomials
Langrange Interpolation PolynomialsLangrange Interpolation Polynomials
Langrange Interpolation Polynomials
 
Word representations in vector space
Word representations in vector spaceWord representations in vector space
Word representations in vector space
 
3.4 deterministic pda
3.4 deterministic pda3.4 deterministic pda
3.4 deterministic pda
 
Contraction mapping
Contraction mappingContraction mapping
Contraction mapping
 
Wordnet
WordnetWordnet
Wordnet
 
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchal
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchalppt on Vector spaces (VCLA) by dhrumil patel and harshid panchal
ppt on Vector spaces (VCLA) by dhrumil patel and harshid panchal
 
Flow Network Talk
Flow Network TalkFlow Network Talk
Flow Network Talk
 
Partial Differentiation
Partial DifferentiationPartial Differentiation
Partial Differentiation
 

En vedette

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
 

En vedette (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
 

Similaire à 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
 

Similaire à 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
 

Dernier

Architecture decision records - How not to get lost in the past
Architecture decision records - How not to get lost in the pastArchitecture decision records - How not to get lost in the past
Architecture decision records - How not to get lost in the pastPapp Krisztián
 
WSO2CON 2024 - Does Open Source Still Matter?
WSO2CON 2024 - Does Open Source Still Matter?WSO2CON 2024 - Does Open Source Still Matter?
WSO2CON 2024 - Does Open Source Still Matter?WSO2
 
WSO2Con2024 - Enabling Transactional System's Exponential Growth With Simplicity
WSO2Con2024 - Enabling Transactional System's Exponential Growth With SimplicityWSO2Con2024 - Enabling Transactional System's Exponential Growth With Simplicity
WSO2Con2024 - Enabling Transactional System's Exponential Growth With SimplicityWSO2
 
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyviewmasabamasaba
 
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...masabamasaba
 
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfonteinmasabamasaba
 
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...Health
 
%in tembisa+277-882-255-28 abortion pills for sale in tembisa
%in tembisa+277-882-255-28 abortion pills for sale in tembisa%in tembisa+277-882-255-28 abortion pills for sale in tembisa
%in tembisa+277-882-255-28 abortion pills for sale in tembisamasabamasaba
 
Direct Style Effect Systems - The Print[A] Example - A Comprehension Aid
Direct Style Effect Systems -The Print[A] Example- A Comprehension AidDirect Style Effect Systems -The Print[A] Example- A Comprehension Aid
Direct Style Effect Systems - The Print[A] Example - A Comprehension AidPhilip Schwarz
 
Software Quality Assurance Interview Questions
Software Quality Assurance Interview QuestionsSoftware Quality Assurance Interview Questions
Software Quality Assurance Interview QuestionsArshad QA
 
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...Bert Jan Schrijver
 
Define the academic and professional writing..pdf
Define the academic and professional writing..pdfDefine the academic and professional writing..pdf
Define the academic and professional writing..pdfPearlKirahMaeRagusta1
 
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...panagenda
 
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...Shane Coughlan
 
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...Steffen Staab
 
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024VictoriaMetrics
 
%in Midrand+277-882-255-28 abortion pills for sale in midrand
%in Midrand+277-882-255-28 abortion pills for sale in midrand%in Midrand+277-882-255-28 abortion pills for sale in midrand
%in Midrand+277-882-255-28 abortion pills for sale in midrandmasabamasaba
 
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️Delhi Call girls
 
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...masabamasaba
 
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...WSO2
 

Dernier (20)

Architecture decision records - How not to get lost in the past
Architecture decision records - How not to get lost in the pastArchitecture decision records - How not to get lost in the past
Architecture decision records - How not to get lost in the past
 
WSO2CON 2024 - Does Open Source Still Matter?
WSO2CON 2024 - Does Open Source Still Matter?WSO2CON 2024 - Does Open Source Still Matter?
WSO2CON 2024 - Does Open Source Still Matter?
 
WSO2Con2024 - Enabling Transactional System's Exponential Growth With Simplicity
WSO2Con2024 - Enabling Transactional System's Exponential Growth With SimplicityWSO2Con2024 - Enabling Transactional System's Exponential Growth With Simplicity
WSO2Con2024 - Enabling Transactional System's Exponential Growth With Simplicity
 
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview
%in Hazyview+277-882-255-28 abortion pills for sale in Hazyview
 
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...
%+27788225528 love spells in Colorado Springs Psychic Readings, Attraction sp...
 
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein
%in kaalfontein+277-882-255-28 abortion pills for sale in kaalfontein
 
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
 
%in tembisa+277-882-255-28 abortion pills for sale in tembisa
%in tembisa+277-882-255-28 abortion pills for sale in tembisa%in tembisa+277-882-255-28 abortion pills for sale in tembisa
%in tembisa+277-882-255-28 abortion pills for sale in tembisa
 
Direct Style Effect Systems - The Print[A] Example - A Comprehension Aid
Direct Style Effect Systems -The Print[A] Example- A Comprehension AidDirect Style Effect Systems -The Print[A] Example- A Comprehension Aid
Direct Style Effect Systems - The Print[A] Example - A Comprehension Aid
 
Software Quality Assurance Interview Questions
Software Quality Assurance Interview QuestionsSoftware Quality Assurance Interview Questions
Software Quality Assurance Interview Questions
 
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...
Devoxx UK 2024 - Going serverless with Quarkus, GraalVM native images and AWS...
 
Define the academic and professional writing..pdf
Define the academic and professional writing..pdfDefine the academic and professional writing..pdf
Define the academic and professional writing..pdf
 
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
 
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...
OpenChain - The Ramifications of ISO/IEC 5230 and ISO/IEC 18974 for Legal Pro...
 
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
 
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024
Large-scale Logging Made Easy: Meetup at Deutsche Bank 2024
 
%in Midrand+277-882-255-28 abortion pills for sale in midrand
%in Midrand+277-882-255-28 abortion pills for sale in midrand%in Midrand+277-882-255-28 abortion pills for sale in midrand
%in Midrand+277-882-255-28 abortion pills for sale in midrand
 
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️
call girls in Vaishali (Ghaziabad) 🔝 >༒8448380779 🔝 genuine Escort Service 🔝✔️✔️
 
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...
%+27788225528 love spells in new york Psychic Readings, Attraction spells,Bri...
 
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...
WSO2CON 2024 - Cloud Native Middleware: Domain-Driven Design, Cell-Based Arch...
 

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