uhc-util-0.1.6.5: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.CHR.Base

Description

Derived from work by Gerrit vd Geest, but with searching structures for predicates to avoid explosion of search space during resolution.

Synopsis

Documentation

class IsConstraint c where Source

The things a constraints needs to be capable of in order to participate in solving

Methods

cnstrRequiresSolve :: c -> Bool Source

Requires solving? Or is just a residue...

Instances

class (CHRMatchable env c subst, VarExtractable c, VarUpdatable c subst, Typeable c, Serialize c, TTKeyable c, IsConstraint c, Ord c, Ord (TTKey c), PP c, PP (TTKey c)) => IsCHRConstraint env c subst Source

(Class alias) API for constraint requirements

data CHRConstraint env subst Source

Constructors

forall c . (IsCHRConstraint env c subst, TTKey (CHRConstraint env subst) ~ TTKey c, ExtrValVarKey (CHRConstraint env subst) ~ ExtrValVarKey c) => CHRConstraint 

Fields

chrConstraint :: c
 

Instances

(~) * (CHRMatchableKey subst) (TTKey (CHRConstraint env subst)) => CHRMatchable env (CHRConstraint env subst) subst Source 
Eq (CHRConstraint env subst) Source 
Ord (CHRConstraint env subst) Source 
Show (CHRConstraint env subst) Source 
PP (CHRConstraint env subst) Source 
TTKeyable (CHRConstraint env subst) Source 
Ord (ExtrValVarKey (CHRConstraint env subst)) => VarExtractable (CHRConstraint env subst) Source 
IsConstraint (CHRConstraint env subst) Source 
VarUpdatable (CHRConstraint env subst) subst Source 
(IsCHRConstraint e c s, (~) * (TTKey (CHRConstraint e s)) (TTKey c), (~) * (ExtrValVarKey (CHRConstraint e s)) (ExtrValVarKey c)) => MkSolverConstraint (CHRConstraint e s) c Source 

class (CHRCheckable env g subst, VarExtractable g, VarUpdatable g subst, Typeable g, Serialize g, PP g) => IsCHRGuard env g subst Source

(Class alias) API for guard requirements

data CHRGuard env subst Source

Constructors

forall g . (IsCHRGuard env g subst, ExtrValVarKey (CHRGuard env subst) ~ ExtrValVarKey g) => CHRGuard 

Fields

chrGuard :: g
 

Instances

CHRCheckable env (CHRGuard env subst) subst Source 
Show (CHRGuard env subst) Source 
PP (CHRGuard env subst) Source 
Ord (ExtrValVarKey (CHRGuard env subst)) => VarExtractable (CHRGuard env subst) Source 
VarUpdatable (CHRGuard env subst) subst Source 
(IsCHRGuard e g s, (~) * (ExtrValVarKey (CHRGuard e s)) (ExtrValVarKey g)) => MkSolverGuard (CHRGuard e s) g Source 

class (CHRPrioEvaluatable env p subst, Typeable p, Serialize p, PP p) => IsCHRPrio env p subst Source

(Class alias) API for priority requirements

Instances

IsCHRPrio env () subst Source 

data CHRPrio env subst Source

Constructors

forall p . IsCHRPrio env p subst => CHRPrio 

Fields

chrPrio :: p
 

Instances

CHRPrioEvaluatable env (CHRPrio env subst) subst Source 
Show (CHRPrio env subst) Source 
PP (CHRPrio env subst) Source 
IsCHRPrio e p s => MkSolverPrio (CHRPrio e s) p Source 

class CHREmptySubstitution subst where Source

Capability to yield an empty substitution.

Methods

chrEmptySubst :: subst Source

class (TTKeyable x, TTKey x ~ CHRMatchableKey subst) => CHRMatchable env x subst where Source

A Matchable participates in the reduction process as a reducable constraint.

Methods

chrMatchTo :: env -> subst -> x -> x -> Maybe subst Source

Instances

(~) * (CHRMatchableKey subst) (TTKey (CHRConstraint env subst)) => CHRMatchable env (CHRConstraint env subst) subst Source 

type family CHRMatchableKey subst :: * Source

class CHRCheckable env x subst where Source

A Checkable participates in the reduction process as a guard, to be checked.

Methods

chrCheck :: env -> subst -> x -> Maybe subst Source

Instances

CHRCheckable env (CHRGuard env subst) subst Source 

class CHRPrioEvaluatable env x subst where Source

A PrioEvaluatable participates in the reduction process to indicate the rule priority, higher prio takes precedence

Methods

chrPrioEval :: env -> subst -> x -> Int Source

Instances

CHRPrioEvaluatable env () subst Source 
CHRPrioEvaluatable env (CHRPrio env subst) subst Source