monadiccp-0.7.7: Constraint Programming

Safe HaskellSafe
LanguageHaskell98

Control.CP.Solver

Synopsis

Documentation

class Monad solver => Solver solver where Source #

Minimal complete definition

add, run, mark, goto

Associated Types

type Constraint solver :: * Source #

the constraints

type Label solver :: * Source #

the labels

Methods

add :: Constraint solver -> solver Bool Source #

add a constraint to the current state, and return whether the resulting state is consistent

run :: solver a -> a Source #

run a computation

mark :: solver (Label solver) Source #

mark the current state, and return its label

markn :: Int -> solver (Label solver) Source #

mark the current state as discontinued, yet return a label that is usable n times

goto :: Label solver -> solver () Source #

go to the state with given label

Instances

Solver OvertonFD Source # 
FDSolver s => Solver (FDInstance s) Source # 

Associated Types

type Constraint (FDInstance s :: * -> *) :: * Source #

type Label (FDInstance s :: * -> *) :: * Source #

(Monoid w, Solver s) => Solver (WriterT w s) Source #

WriterT decoration of a solver useful for producing statistics during solving

Associated Types

type Constraint (WriterT w s :: * -> *) :: * Source #

type Label (WriterT w s :: * -> *) :: * Source #

Methods

add :: Constraint (WriterT w s) -> WriterT w s Bool Source #

run :: WriterT w s a -> a Source #

mark :: WriterT w s (Label (WriterT w s)) Source #

markn :: Int -> WriterT w s (Label (WriterT w s)) Source #

goto :: Label (WriterT w s) -> WriterT w s () Source #

add :: Solver solver => Constraint solver -> solver Bool Source #

add a constraint to the current state, and return whether the resulting state is consistent

run :: Solver solver => solver a -> a Source #

run a computation

mark :: Solver solver => solver (Label solver) Source #

mark the current state, and return its label

markn :: Solver solver => Int -> solver (Label solver) Source #

mark the current state as discontinued, yet return a label that is usable n times

goto :: Solver solver => Label solver -> solver () Source #

go to the state with given label

class Solver solver => Term solver term where Source #

Minimal complete definition

newvar, help

Associated Types

type Help solver term Source #

Methods

newvar :: solver term Source #

produce a fresh constraint variable

help :: solver () -> term -> Help solver term Source #

Instances

Term OvertonFD FDVar Source # 

Associated Types

type Help (OvertonFD :: * -> *) FDVar :: * Source #

FDSolver s => Term (FDInstance s) ModelCol Source # 

Associated Types

type Help (FDInstance s :: * -> *) ModelCol :: * Source #

FDSolver s => Term (FDInstance s) ModelBool Source # 

Associated Types

type Help (FDInstance s :: * -> *) ModelBool :: * Source #

FDSolver s => Term (FDInstance s) ModelInt Source # 

Associated Types

type Help (FDInstance s :: * -> *) ModelInt :: * Source #

(Monoid w, Term s t) => Term (WriterT w s) t Source # 

Associated Types

type Help (WriterT w s :: * -> *) t :: * Source #

Methods

newvar :: WriterT w s t Source #

help :: WriterT w s () -> t -> Help (WriterT w s) t Source #

newvar :: Term solver term => solver term Source #

produce a fresh constraint variable

help :: Term solver term => solver () -> term -> Help solver term Source #