chr-core-0.1.0.4: Constraint Handling Rules

Safe HaskellNone
LanguageHaskell2010

CHR.Types.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

Instances
Show (RuleBodyAlt c bp) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

showsPrec :: Int -> RuleBodyAlt c bp -> ShowS #

show :: RuleBodyAlt c bp -> String #

showList :: [RuleBodyAlt c bp] -> ShowS #

VarExtractable c => VarExtractable (RuleBodyAlt c p) Source # 
Instance details

Defined in CHR.Types.Rule

(PP bp, PP c) => PP (RuleBodyAlt c bp) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

pp :: RuleBodyAlt c bp -> PP_Doc #

ppList :: [RuleBodyAlt c bp] -> PP_Doc #

(VarUpdatable c s, VarUpdatable p s) => VarUpdatable (RuleBodyAlt c p) s Source # 
Instance details

Defined in CHR.Types.Rule

Methods

varUpd :: s -> RuleBodyAlt c p -> RuleBodyAlt c p #

varUpdCyc :: s -> RuleBodyAlt c p -> (RuleBodyAlt c p, VarMp' (VarLookupKey s) (VarLookupVal s)) #

type ExtrValVarKey (RuleBodyAlt c p) Source # 
Instance details

Defined in CHR.Types.Rule

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

Instances
Show (Rule c g bp p) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

showsPrec :: Int -> Rule c g bp p -> ShowS #

show :: Rule c g bp p -> String #

showList :: [Rule c g bp p] -> ShowS #

(VarExtractable c, VarExtractable g, ExtrValVarKey c ~ ExtrValVarKey g) => VarExtractable (Rule c g bp p) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

varFree :: Rule c g bp p -> [ExtrValVarKey (Rule c g bp p)] #

varFreeSet :: Rule c g bp p -> Set (ExtrValVarKey (Rule c g bp p)) #

TreeTrieKeyable cnstr => TreeTrieKeyable (Rule cnstr guard bprio prio) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

toTreeTriePreKey1 :: Rule cnstr guard bprio prio -> PreKey1 (Rule cnstr guard bprio prio) #

(PP c, PP g, PP p, PP bp) => PP (Rule c g bp p) Source # 
Instance details

Defined in CHR.Types.Rule

Methods

pp :: Rule c g bp p -> PP_Doc #

ppList :: [Rule c g bp p] -> PP_Doc #

(VarUpdatable c s, VarUpdatable g s, VarUpdatable bp s, VarUpdatable p s) => VarUpdatable (Rule c g bp p) s Source # 
Instance details

Defined in CHR.Types.Rule

Methods

varUpd :: s -> Rule c g bp p -> Rule c g bp p #

varUpdCyc :: s -> Rule c g bp p -> (Rule c g bp p, VarMp' (VarLookupKey s) (VarLookupVal s)) #

type ExtrValVarKey (Rule c g bp p) Source # 
Instance details

Defined in CHR.Types.Rule

type ExtrValVarKey (Rule c g bp p) = ExtrValVarKey c
type TrTrKey (Rule cnstr guard bprio prio) Source # 
Instance details

Defined in CHR.Types.Rule

type TrTrKey (Rule cnstr guard bprio prio) = TrTrKey cnstr

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], 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

(<=>) :: [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 prio1 -> prio2 -> Rule cnstr guard bprio prio2 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