monadiccp-0.7.5: Constraint Programming

Safe HaskellNone

Control.CP.FD.Interface

Synopsis

Documentation

class (Solver s, Term s (FDIntTerm s), Term s (FDBoolTerm s), Eq (FDBoolSpecType s), Ord (FDBoolSpecType s), Enum (FDBoolSpecType s), Bounded (FDBoolSpecType s), Show (FDBoolSpecType s), Eq (FDIntSpecType s), Ord (FDIntSpecType s), Enum (FDIntSpecType s), Bounded (FDIntSpecType s), Show (FDIntSpecType s), Eq (FDColSpecType s), Ord (FDColSpecType s), Enum (FDColSpecType s), Bounded (FDColSpecType s), Show (FDColSpecType s), Show (FDIntSpec s), Show (FDColSpec s), Show (FDBoolSpec s)) => FDSolver s Source

A solver needs to be an instance of this FDSolver class in order to create an FDInstance around it.

data FDSolver s => FDInstance s a Source

definition of FDInstance, a Solver wrapper that adds power to post boolean expressions as constraints

(@+) :: (Eq t, Eq c, Eq b, ToExpr t c b p, ToExpr t c b q) => p -> q -> Expr t c bSource

integer operators/functions | --

(@-) :: (Eq t, Eq c, Eq b, ToExpr t c b p, ToExpr t c b q) => p -> q -> Expr t c bSource

(@*) :: (Eq t, Eq c, Eq b, ToExpr t c b p, ToExpr t c b q) => p -> q -> Expr t c bSource

(@/) :: (Eq t, Eq c, Eq b, ToExpr t c b p, ToExpr t c b q) => p -> q -> Expr t c bSource

(@%) :: (Eq t, Eq c, Eq b, ToExpr t c b p, ToExpr t c b q) => p -> q -> Expr t c bSource

(!) :: (Eq t, Eq c, Eq b) => ColExpr t c b -> Expr t c b -> Expr t c bSource

list operators/functions | --

(@!!) :: (Eq t, Eq c, Eq b) => ColExpr t c b -> Integer -> Expr t c bSource

(@..) :: (Eq t, Eq c, Eq b) => Expr t c b -> Expr t c b -> ColExpr t c bSource

(@++) :: (Eq t, Eq c, Eq b) => ColExpr t c b -> ColExpr t c b -> ColExpr t c bSource

size :: (Eq t, Eq c, Eq b) => ColExpr t c b -> Expr t c bSource

xfold :: (Eq t, Eq c, Eq b) => (Expr t c b -> Expr t c b -> Expr t c b) -> Expr t c b -> ColExpr t c b -> Expr t c bSource

xsum :: (Num (Expr t c b), Eq t, Eq c, Eq b) => ColExpr t c b -> Expr t c bSource

xhead :: (Eq t, Eq c, Eq b, ToColExpr t c b p) => p -> Expr t c bSource

xtail :: (Eq t, Eq c, Eq b, ToColExpr t c b p) => p -> ColExpr t c bSource

list :: (Eq t, Eq c, Eq b) => [Expr t c b] -> ColExpr t c bSource

slice :: (Eq t, Eq c, Eq b) => ColExpr t c b -> ColExpr t c b -> ColExpr t c bSource

xmap :: (Eq t, Eq c, Eq b) => (Expr t c b -> Expr t c b) -> ColExpr t c b -> ColExpr t c bSource

(@||) :: (Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => Tree DummySolver () -> Tree DummySolver () -> m ()Source

(@&&) :: (Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => Tree DummySolver () -> Tree DummySolver () -> m ()Source

inv :: (Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => Tree DummySolver () -> m ()Source

(@=) :: (ModelExprClass a, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => a -> a -> m ()Source

(@/=) :: (ModelExprClass a, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => a -> a -> m ()Source

(@??) :: (MonadTree m, ~ * (Constraint (TreeSolver m)) (Either Model q)) => Tree DummySolver () -> (Tree DummySolver (), Tree DummySolver ()) -> m ()Source

channel :: Tree DummySolver () -> ModelIntSource

val :: Tree DummySolver () -> ModelIntSource

forall :: (Term s ModelInt, Term s ModelBool, Term s ModelCol, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => ModelCol -> (ModelInt -> Tree DummySolver ()) -> m ()Source

forany :: (Term s ModelInt, Term s ModelBool, Term s ModelCol, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => ModelCol -> (ModelInt -> Tree DummySolver ()) -> m ()Source

loopall :: (Term s ModelInt, Term s ModelBool, Term s ModelCol, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => (ModelInt, ModelInt) -> (ModelInt -> Tree DummySolver ()) -> m ()Source

loopany :: (Term s ModelInt, Term s ModelBool, Term s ModelCol, Constraint s ~ Either Model q, MonadTree m, TreeSolver m ~ s) => (ModelInt, ModelInt) -> (ModelInt -> Tree DummySolver ()) -> m ()Source

type ModelInt = ModelIntExpr ModelFunctionsSource

type ModelCol = ModelColExpr ModelFunctionsSource

type ModelBool = ModelBoolExpr ModelFunctionsSource

exists :: (MonadTree m, Term (TreeSolver m) t) => (t -> m a) -> m aSource

true :: MonadTree tree => tree ()Source