uhc-util-0.1.6.6: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.CHR.Rule

Description

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

Synopsis

Documentation

data RuleBodyAlt cnstr bprio Source

Constructors

RuleBodyAlt 

Fields

rbodyaltBacktrackPrio :: !(Maybe bprio)

optional backtrack priority, if absent it is inherited from the active backtrack prio

rbodyaltBody :: ![cnstr]

body constraints to be dealt with by rules , rbodyaltBodyBuiltin :: ![builtin] -- ^ builtin constraints to be dealt with by builtin solving

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.

Constructors

Rule 

Fields

ruleHead :: ![cnstr]
 
ruleSimpSz :: !Int

length of the part of the head which is the simplification part

ruleGuard :: ![guard]
 
ruleBodyAlts :: ![RuleBodyAlt cnstr bprio]
 
ruleBacktrackPrio :: !(Maybe bprio)

backtrack priority, should be something which can be substituted with the actual prio, later to be referred to at backtrack prios of alternatives

rulePrio :: !(Maybe prio)

rule priority, to choose between rules with equal backtrack priority

ruleName :: Maybe String
 

Instances

Show (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 
(VarExtractable c, VarExtractable g, (~) * (ExtrValVarKey c) (ExtrValVarKey g)) => VarExtractable (Rule c g bp p) Source 
(VarUpdatable c s, VarUpdatable g s, VarUpdatable bp s, VarUpdatable p s) => VarUpdatable (Rule c g bp p) s Source 
type TTKey (Rule cnstr guard bprio prio) = TTKey cnstr Source 
type ExtrValVarKey (Rule c g bp p) = ExtrValVarKey c 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

ruleSz :: Rule c g bp p -> Int Source

Total nr of cnstrs in rule

(/\) :: [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], t) -> Rule a guard bprio prio Source

Construct simplification rule out of head, body, and builtin constraints

(==>>) :: [cnstr] -> ([cnstr], t) -> Rule cnstr guard bprio prio Source

Construct propagation rule out of head, body, and builtin constraints

(<\>>) :: ([a], [a]) -> ([a], t) -> 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

(<=>) :: [a] -> [a] -> Rule a guard bprio prio infix 3 Source

(==>) :: [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 -> [guard] -> Rule cnstr guard bprio prio infixl 2 Source

(=!) :: Rule cnstr guard bprio prio -> bprio -> Rule cnstr guard bprio prio infixl 2 Source

Add backtrack priority to rule

(=!!) :: Rule cnstr guard bprio t -> prio -> Rule cnstr guard bprio prio infixl 2 Source

Add priority to rule

(=@) :: Rule cnstr guard bprio prio -> String -> Rule cnstr guard bprio prio infixl 2 Source

Add label to rule

(@=) :: String -> Rule cnstr guard bprio prio -> Rule cnstr guard bprio prio infixr 1 Source

Add label to rule