monadiccp-0.7.4: Constraint Programming

Safe HaskellSafe-Infered

Data.Expr.Sugar

Synopsis

Documentation

(@+) :: (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) => BoolExpr t c b -> (Expr t c b, Expr t c b) -> Expr t c bSource

(@??) :: (Eq t, Eq c, Eq b) => BoolExpr t c b -> (BoolExpr t c b, BoolExpr t c b) -> BoolExpr 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) => ColExpr t c b -> ColExpr t c b -> ColExpr t c bSource

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

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

slice :: (Eq t, Eq c, Eq b) => ColExpr t c b -> ColExpr t c b -> ColExpr 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

xmap :: (Eq t, Eq c, Eq b) => (Expr t c b -> Expr t c b) -> ColExpr t c b -> ColExpr 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

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

channel :: (Eq t, Eq c, Eq b) => BoolExpr 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

(@||) :: (Eq b, Eq c, Eq s, ToBoolExpr s c b b2, ToBoolExpr s c b b1) => b1 -> b2 -> BoolExpr s c bSource

(@&&) :: (Eq b, Eq c, Eq s, ToBoolExpr s c b b2, ToBoolExpr s c b b1) => b1 -> b2 -> BoolExpr s c bSource

inv :: (Eq t, Eq c, Eq b, ToBoolExpr t c b p) => p -> BoolExpr t c bSource

boolean operators/functions | --

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

(@<) :: (Eq t, Eq c, Eq b) => Expr t c b -> Expr t c b -> BoolExpr t c bSource

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

(@<=) :: (Eq t, Eq c, Eq b) => Expr t c b -> Expr t c b -> BoolExpr t c bSource

loopall :: (Eq t, Eq c, Eq b) => (Expr t c b, Expr t c b) -> (Expr t c b -> BoolExpr t c b) -> BoolExpr t c bSource

loopany :: (Eq t, Eq c, Eq b) => (Expr t c b, Expr t c b) -> (Expr t c b -> BoolExpr t c b) -> BoolExpr t c bSource

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

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

data Expr t c b Source

Data types | --

Instances

ModelTermType ModelInt 
ModelExprClass ModelInt 
Procable GecodeListConst 
Procable GecodeIntConst 
(Eq b, Eq a, Eq t) => ToColExpr t a b [Expr t a b] 
(Eq t, Eq c, Eq b) => ExprRange t c b (Expr t c b, Expr t c b) 
(Eq t, Eq c, Eq b) => ExprClass t c b (Expr t c b)

relational operators/functions | --

(Eq t, Eq a, Eq b) => ToColExpr t a b (Expr t a b) 
ToExpr t a b (Expr t a b) 
FDSolver s => Term (FDInstance s) ModelInt 
(FDSolver s, EnumTerm s (FDIntTerm s)) => EnumTerm (FDInstance s) ModelInt 
Eq (EGPar -> EGPar) 
Ord (EGPar -> EGPar) 
Show (EGPar -> EGPar) 
Show (GecodeIntConst -> GecodeIntConst) 
(Show t, Show c, Show b, ShowFn e) => ShowFn (Expr t c b -> e) 
Procable (a, GecodeListConst) 
CompilableModel m => CompilableModel (ModelInt -> m) 
CompilableModel (FDInstance (GecodeWrappedSolver CodegenGecodeSolver) (SearchSpec ModelInt ModelCol ModelBool)) 
(Eq s, Eq c, Eq b) => Enum (Expr s c b) 
(Eq t, Eq c, Eq b) => Eq (Expr t c b) 
(Ord s, Ord c, Ord b, Eq s, Eq c, Eq b, Show s, Show c, Show b) => Integral (Expr s c b) 
(Eq s, Eq c, Eq b, Show s, Show c, Show b) => Num (Expr s c b)

Built-in class instances | --

(Ord s, Ord c, Ord b) => Ord (Expr s c b) 
(Ord s, Ord c, Ord b, Eq s, Eq c, Eq b, Show s, Show c, Show b) => Real (Expr s c b) 
(Show t, Show c, Show b) => Show (Expr t c b) 
(Show t, Show c, Show b) => ShowFn (Expr t c b) 

data ColExpr t c b Source

Instances

ModelTermType ModelCol 
ModelExprClass ModelCol 
Procable GecodeColConst 
(Eq t, Eq c, Eq b) => ExprRange t c b (ColExpr t c b) 
(Eq t, Eq c, Eq b) => ExprClass t c b (ColExpr t c b) 
ToColExpr t a b (ColExpr t a b) 
FDSolver s => Term (FDInstance s) ModelCol 
CompilableModel m => CompilableModel (ModelCol -> m) 
CompilableModel (Tree (FDInstance (GecodeWrappedSolver CodegenGecodeSolver)) ModelCol) 
CompilableModel (FDInstance (GecodeWrappedSolver CodegenGecodeSolver) ModelCol) 
CompilableModel (FDInstance (GecodeWrappedSolver CodegenGecodeSolver) (SearchSpec ModelInt ModelCol ModelBool)) 
(Eq t, Eq c, Eq b) => Eq (ColExpr t c b) 
(Ord s, Ord c, Ord b) => Ord (ColExpr s c b) 
(Show t, Show c, Show b) => Show (ColExpr t c b) 
(Show t, Show c, Show b) => ShowFn (ColExpr t c b) 

data BoolExpr t c b Source

Instances

ModelTermType ModelBool 
ModelExprClass ModelBool 
Procable GecodeBoolConst 
(Eq t, Eq c, Eq b) => ExprClass t c b (BoolExpr t c b) 
ToBoolExpr t a b (BoolExpr t a b) 
(Eq t, Eq a, Eq b) => ToExpr t a b (BoolExpr t a b) 
FDSolver s => Term (FDInstance s) ModelBool 
(FDSolver s, EnumTerm s (FDBoolTerm s)) => EnumTerm (FDInstance s) ModelBool 
CompilableModel (FDInstance (GecodeWrappedSolver CodegenGecodeSolver) (SearchSpec ModelInt ModelCol ModelBool)) 
(Eq t, Eq c, Eq b) => Eq (BoolExpr t c b) 
(Ord s, Ord c, Ord b) => Ord (BoolExpr s c b) 
(Show t, Show c, Show b) => Show (BoolExpr t c b) 
(Show t, Show c, Show b) => ShowFn (BoolExpr t c b) 

class ToExpr tt cc bb t whereSource

convertion from/to expression types | --

Methods

toExpr :: t -> Expr tt cc bbSource

Instances

ToExpr t a b t 
ToExpr tt cc bb Int 
ToExpr tt cc bb Integer 
(Eq t, Eq a, Eq b) => ToExpr t a b (BoolExpr t a b) 
ToExpr t a b (Expr t a b) 

class ToColExpr tt cc bb c whereSource

Methods

toColExpr :: c -> ColExpr tt cc bbSource

Instances

ToColExpr t a b a 
(Eq b, Eq a, Eq t) => ToColExpr t a b [Expr t a b] 
(Eq t, Eq a, Eq b) => ToColExpr t a b (Expr t a b) 
ToColExpr t a b (ColExpr t a b) 

class ToBoolExpr tt cc bb b whereSource

Methods

toBoolExpr :: b -> BoolExpr tt cc bbSource

Instances

ToBoolExpr t a b b 
ToBoolExpr tt cc bb Bool 
ToBoolExpr t a b (BoolExpr t a b) 

sorted :: (Eq b, Eq c, Eq s) => ColExpr s c b -> BoolExpr s c bSource

sSorted :: (Eq b, Eq c, Eq s) => ColExpr s c b -> BoolExpr s c bSource

allDiff :: (Eq b, Eq c, Eq s) => ColExpr s c b -> BoolExpr s c bSource

allDiffD :: (Eq b, Eq c, Eq s) => ColExpr s c b -> BoolExpr s c bSource

class (Eq tt, Eq cc, Eq bb) => ExprClass tt cc bb a whereSource

Methods

(@=) :: a -> a -> BoolExpr tt cc bbSource

(@/=) :: a -> a -> BoolExpr tt cc bbSource

Instances

(Eq t, Eq c, Eq b) => ExprClass t c b (ColExpr t c b) 
(Eq t, Eq c, Eq b) => ExprClass t c b (BoolExpr t c b) 
(Eq t, Eq c, Eq b) => ExprClass t c b (Expr t c b)

relational operators/functions | --

class (Eq tt, Eq cc, Eq bb) => ExprRange tt cc bb r whereSource

Methods

(@:) :: Expr tt cc bb -> r -> BoolExpr tt cc bbSource

Instances

(Eq t, Eq c, Eq b) => ExprRange t c b (Expr t c b, Expr t c b) 
(Eq t, Eq c, Eq b) => ExprRange t c b (ColExpr t c b)