Safe Haskell | None |
---|---|
Language | Haskell98 |
The representation of rules, which should allow an implementation of:
"A Flexible Search Framework for CHR", Leslie De Koninck, Tom Schrijvers, and Bart Demoen. http:/link.springer.com10.1007/978-3-540-92243-8_2
- data RuleBodyAlt cnstr bprio = RuleBodyAlt {
- rbodyaltBacktrackPrio :: !(Maybe bprio)
- rbodyaltBody :: ![cnstr]
- data Rule cnstr guard bprio prio = Rule {
- ruleHead :: ![cnstr]
- ruleSimpSz :: !Int
- ruleGuard :: ![guard]
- ruleBodyAlts :: ![RuleBodyAlt cnstr bprio]
- ruleBacktrackPrio :: !(Maybe bprio)
- rulePrio :: !(Maybe prio)
- ruleName :: Maybe String
- ruleBody :: Rule c g bp p -> [c]
- ruleBody' :: Rule c g bp p -> ([c], [c])
- ruleSz :: Rule c g bp p -> Int
- (/\) :: [c] -> [c] -> RuleBodyAlt c p
- (\/) :: [RuleBodyAlt c p] -> [RuleBodyAlt c p] -> [RuleBodyAlt c p]
- (\!) :: RuleBodyAlt c p -> p -> RuleBodyAlt c p
- (<=>>) :: [a] -> ([a], p) -> Rule a guard bprio prio
- (==>>) :: [cnstr] -> ([cnstr], p) -> Rule cnstr guard bprio prio
- (<\>>) :: ([a], [a]) -> ([a], p) -> Rule a guard bprio prio
- (<==>) :: [a] -> [a] -> Rule a guard bprio prio
- (<=>) :: [a] -> [a] -> Rule a guard bprio prio
- (==>) :: [cnstr] -> [cnstr] -> Rule cnstr guard bprio prio
- (<\>) :: ([a], [a]) -> [a] -> Rule a guard bprio prio
- (|>) :: Rule cnstr guard bprio prio -> [guard] -> Rule cnstr guard bprio prio
- (=|) :: Rule cnstr guard bprio prio -> [guard] -> Rule cnstr guard bprio prio
- (=!) :: Rule cnstr guard bprio prio -> bprio -> Rule cnstr guard bprio prio
- (=!!) :: Rule cnstr guard bprio prio1 -> prio2 -> Rule cnstr guard bprio prio2
- (=@) :: Rule cnstr guard bprio prio -> String -> Rule cnstr guard bprio prio
- (@=) :: String -> Rule cnstr guard bprio prio -> Rule cnstr guard bprio prio
Documentation
data RuleBodyAlt cnstr bprio Source #
RuleBodyAlt | |
|
Show (RuleBodyAlt c bp) Source # | |
VarExtractable c => VarExtractable (RuleBodyAlt c p) Source # | |
(PP bp, PP c) => PP (RuleBodyAlt c bp) Source # | |
(Serialize c, Serialize p) => Serialize (RuleBodyAlt c p) Source # | |
(VarUpdatable c s, VarUpdatable p s) => VarUpdatable (RuleBodyAlt c p) s Source # | |
type ExtrValVarKey (RuleBodyAlt c p) Source # | |
data Rule cnstr guard bprio prio Source #
A CHR (rule) consist of head (simplification + propagation, boundary indicated by an Int), guard, and a body. All may be empty, but not all at the same time.
Rule | |
|
Show (Rule c g bp p) Source # | |
(VarExtractable c, VarExtractable g, (~) * (ExtrValVarKey c) (ExtrValVarKey g)) => VarExtractable (Rule c g bp p) Source # | |
(PP c, PP g, PP p, PP bp) => PP (Rule c g bp p) Source # | |
(Serialize c, Serialize g, Serialize bp, Serialize p) => Serialize (Rule c g bp p) Source # | |
TTKeyable cnstr => TTKeyable (Rule cnstr guard bprio prio) Source # | |
(VarUpdatable c s, VarUpdatable g s, VarUpdatable bp s, VarUpdatable p s) => VarUpdatable (Rule c g bp p) s Source # | |
type ExtrValVarKey (Rule c g bp p) Source # | |
type TTKey (Rule cnstr guard bprio prio) Source # | |
ruleBody :: Rule c g bp p -> [c] Source #
Backwards compatibility: if only one alternative, extract it, ignore other alts
ruleBody' :: Rule c g bp p -> ([c], [c]) Source #
Backwards compatibility: if only one alternative, extract it, ignore other alts
(/\) :: [c] -> [c] -> RuleBodyAlt c p infixl 6 Source #
Rule body backtracking alternative
(\/) :: [RuleBodyAlt c p] -> [RuleBodyAlt c p] -> [RuleBodyAlt c p] infixr 4 Source #
Rule body backtracking alternatives
(\!) :: RuleBodyAlt c p -> p -> RuleBodyAlt c p infixl 5 Source #
Add backtrack priority to body alternative
(<=>>) :: [a] -> ([a], p) -> Rule a guard bprio prio Source #
Construct simplification rule out of head, body, and builtin constraints
(==>>) :: [cnstr] -> ([cnstr], p) -> Rule cnstr guard bprio prio Source #
Construct propagation rule out of head, body, and builtin constraints
(<\>>) :: ([a], [a]) -> ([a], p) -> Rule a guard bprio prio Source #
Construct simpagation rule out of head, body, and builtin constraints
(<==>) :: [a] -> [a] -> Rule a guard bprio prio infix 3 Source #
Construct simplification rule out of head and body constraints
(==>) :: [cnstr] -> [cnstr] -> Rule cnstr guard bprio prio infix 3 Source #
Construct propagation rule out of head and body constraints
(<\>) :: ([a], [a]) -> [a] -> Rule a guard bprio prio infix 3 Source #
Construct simpagation rule out of head and body constraints
(|>) :: Rule cnstr guard bprio prio -> [guard] -> Rule cnstr guard bprio prio infixl 2 Source #
Deprecated: Use (=|)
Add guards to rule
(=!) :: Rule cnstr guard bprio prio -> bprio -> Rule cnstr guard bprio prio infixl 2 Source #
Add backtrack priority to rule
(=!!) :: Rule cnstr guard bprio prio1 -> prio2 -> Rule cnstr guard bprio prio2 infixl 2 Source #
Add priority to rule