monadiccp-0.7.6: Constraint Programming

Safe HaskellSafe-Inferred

Data.Expr.Data

Synopsis

Documentation

data Expr t c b Source

Data types | --

Constructors

Term t 
ExprHole Int 
Const Integer 
Plus (Expr t c b) (Expr t c b) 
Minus (Expr t c b) (Expr t c b) 
Mult (Expr t c b) (Expr t c b) 
Div (Expr t c b) (Expr t c b) 
Mod (Expr t c b) (Expr t c b) 
Abs (Expr t c b) 
At (ColExpr t c b) (Expr t c b) 
Fold (Expr t c b -> Expr t c b -> Expr t c b) (Expr t c b) (ColExpr t c b) 
Cond (BoolExpr t c b) (Expr t c b) (Expr t c b) 
ColSize (ColExpr t c b) 
Channel (BoolExpr t c b) 

Instances

ModelTermType ModelInt 
(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) 
(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) 

data ColExpr t c b Source

Constructors

ColTerm c 
ColList [Expr t c b] 
ColRange (Expr t c b) (Expr t c b) 
ColMap (Expr t c b -> Expr t c b) (ColExpr t c b) 
ColSlice (Expr t c b -> Expr t c b) (Expr t c b) (ColExpr t c b) 
ColCat (ColExpr t c b) (ColExpr t c b) 

Instances

ModelTermType ModelCol 
(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 
(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) 

data BoolExpr t c b Source

Constructors

BoolTerm b 
BoolConst Bool 
BoolAnd (BoolExpr t c b) (BoolExpr t c b) 
BoolOr (BoolExpr t c b) (BoolExpr t c b) 
BoolNot (BoolExpr t c b) 
BoolCond (BoolExpr t c b) (BoolExpr t c b) (BoolExpr t c b) 
Rel (Expr t c b) ExprRel (Expr t c b) 
BoolAll (Expr t c b -> BoolExpr t c b) (ColExpr t c b) 
BoolAny (Expr t c b -> BoolExpr t c b) (ColExpr t c b) 
ColEqual (ColExpr t c b) (ColExpr t c b) 
BoolEqual (BoolExpr t c b) (BoolExpr t c b) 
AllDiff Bool (ColExpr t c b) 
Sorted Bool (ColExpr t c b) 
Dom (Expr t c b) (ColExpr t c b) 

Instances

ModelTermType ModelBool 
(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 
(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) 

data ExprRel Source

Constructors

EREqual 
ERDiff 
ERLess 

(<<>>) :: Ordering -> Ordering -> OrderingSource

ExprKey: Provides ordering over expressions | --