monadiccp-0.7.6: Constraint Programming

Safe HaskellSafe-Inferred

Data.Expr.Util

Synopsis

Documentation

data Expr t c b Source

Data types | --

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 BoolExpr t c b Source

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 ColExpr t c b Source

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) 

transform :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> b, c -> d, e -> f, b -> a, d -> c, f -> e) -> Expr a c e -> Expr b d fSource

Transform expressions over one type to expressions over another | --

colTransform :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> b, c -> d, e -> f, b -> a, d -> c, f -> e) -> ColExpr a c e -> ColExpr b d fSource

boolTransform :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> b, c -> d, e -> f, b -> a, d -> c, f -> e) -> BoolExpr a c e -> BoolExpr b d fSource

transformEx :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> Expr b d f, c -> ColExpr b d f, e -> BoolExpr b d f, b -> Expr a c e, d -> ColExpr a c e, f -> BoolExpr a c e) -> Expr a c e -> Expr b d fSource

colTransformEx :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> Expr b d f, c -> ColExpr b d f, e -> BoolExpr b d f, b -> Expr a c e, d -> ColExpr a c e, f -> BoolExpr a c e) -> ColExpr a c e -> ColExpr b d fSource

boolTransformEx :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => (a -> Expr b d f, c -> ColExpr b d f, e -> BoolExpr b d f, b -> Expr a c e, d -> ColExpr a c e, f -> BoolExpr a c e) -> BoolExpr a c e -> BoolExpr b d fSource

property :: (a -> Bool) -> (b -> Bool) -> (c -> Bool) -> Expr a b c -> BoolSource

colProperty :: (a -> Bool) -> (b -> Bool) -> (c -> Bool) -> ColExpr a b c -> BoolSource

boolProperty :: (a -> Bool) -> (b -> Bool) -> (c -> Bool) -> BoolExpr a b c -> BoolSource

propertyEx :: (Expr a b c -> Maybe Bool, ColExpr a b c -> Maybe Bool, BoolExpr a b c -> Maybe Bool) -> Expr a b c -> BoolSource

Check whether an expression is possibly referring to terms with a given property | --

colPropertyEx :: (Expr a b c -> Maybe Bool, ColExpr a b c -> Maybe Bool, BoolExpr a b c -> Maybe Bool) -> ColExpr a b c -> BoolSource

boolPropertyEx :: (Expr a b c -> Maybe Bool, ColExpr a b c -> Maybe Bool, BoolExpr a b c -> Maybe Bool) -> BoolExpr a b c -> BoolSource

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

Turn expressions over expressions into simply expressions | --

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

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

simplify :: (Eq s, Eq c, Eq b) => Expr s c b -> Expr s c bSource

Simplify expressions | --

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

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

data WalkPhase Source

walk through expressions

Constructors

WalkPre 
WalkSingle 
WalkPost 

walk :: (Eq t, Eq c, Eq b, Monad m) => Expr t c b -> (Expr t c b -> WalkPhase -> m WalkResult, ColExpr t c b -> WalkPhase -> m WalkResult, BoolExpr t c b -> WalkPhase -> m WalkResult) -> m ()Source

colWalk :: (Eq t, Eq c, Eq b, Monad m) => ColExpr t c b -> (Expr t c b -> WalkPhase -> m WalkResult, ColExpr t c b -> WalkPhase -> m WalkResult, BoolExpr t c b -> WalkPhase -> m WalkResult) -> m ()Source

boolWalk :: (Eq t, Eq c, Eq b, Monad m) => BoolExpr t c b -> (Expr t c b -> WalkPhase -> m WalkResult, ColExpr t c b -> WalkPhase -> m WalkResult, BoolExpr t c b -> WalkPhase -> m WalkResult) -> m ()Source