uhc-util-0.1.6.7: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.CHR.Base

Contents

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

cnstrSolvesVia :: c -> ConstraintSolvesVia Source #

data ConstraintSolvesVia Source #

Different ways of solving

Constructors

ConstraintSolvesVia_Rule

rewrite/CHR rules apply

ConstraintSolvesVia_Solve

solving involving finding of variable bindings (e.g. unification)

ConstraintSolvesVia_Residual

a leftover, residue

ConstraintSolvesVia_Fail

triggers explicit fail

ConstraintSolvesVia_Succeed

triggers explicit succes

Instances

Enum ConstraintSolvesVia Source # 
Eq ConstraintSolvesVia Source # 
Ord ConstraintSolvesVia Source # 
Show ConstraintSolvesVia Source # 
PP ConstraintSolvesVia Source # 

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

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

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

(Class alias) API for priority requirements

class (IsCHRPrio env bp subst, CHRMatchable env bp subst, PP (CHRPrioEvaluatableVal bp)) => IsCHRBacktrackPrio env bp subst Source #

(Class alias) API for backtrack priority requirements

class CHREmptySubstitution subst where Source #

Capability to yield an empty substitution.

Minimal complete definition

chrEmptySubst

Methods

chrEmptySubst :: subst Source #

data CHRMatcherFailure Source #

Failure of CHRMatcher

Constructors

CHRMatcherFailure 
CHRMatcherFailure_NoBinding

absence of binding

type CHRMatcher subst = StateT (CHRMatcherState subst (VarLookupKey subst)) (Either CHRMatcherFailure) Source #

Matching monad, keeping a stacked (pair) of subst (local + global), and a set of global variables upon which the solver has to wait in order to (possibly) match further/again type CHRMatcher subst = StateT (StackedVarLookup subst, CHRWaitForVarSet subst) (Either ())

chrmatcherRun' :: CHREmptySubstitution subst => (CHRMatcherFailure -> r) -> (subst -> CHRWaitForVarSet subst -> x -> r) -> CHRMatcher subst x -> CHRMatchEnv (VarLookupKey subst) -> StackedVarLookup subst -> r Source #

Run a CHRMatcher

chrmatcherRun :: CHREmptySubstitution subst => CHRMatcher subst () -> CHRMatchEnv (VarLookupKey subst) -> subst -> Maybe (subst, CHRWaitForVarSet subst) Source #

Run a CHRMatcher

chrmatcherstateEnv :: ArrowApply arr => Lens arr ((a, b, c) -> (a, b, o)) (c -> o) Source #

chrmatcherstateVarLookup :: ArrowApply arr => Lens arr ((a, b, c) -> (o, b, c)) (a -> o) Source #

chrMatchResolveCompareAndContinue Source #

Arguments

:: (VarLookup s, VarLookupCmb s s, Ord (VarLookupKey s), VarTerm (VarLookupVal s), ExtrValVarKey (VarLookupVal s) ~ VarLookupKey s) 
=> CHRMatchHow

how to do the resolution

-> (VarLookupVal s -> VarLookupVal s -> CHRMatcher s ())

succeed with successful varlookup continuation

-> VarLookupVal s

left/fst val

-> VarLookupVal s

right/snd val

-> CHRMatcher s () 

Do the resolution part of a comparison, continuing with a function which can assume variable resolution has been done for the terms being compared

chrMatchBind :: forall subst k v. (VarLookupCmb subst subst, VarLookup subst, k ~ VarLookupKey subst, v ~ VarLookupVal subst) => k -> v -> CHRMatcher subst () Source #

chrMatchFail :: CHRMatcher subst a Source #

Normal CHRMatcher failure

chrMatchFailNoBinding :: CHRMatcher subst a Source #

CHRMatcher failure because a variable binding is missing

chrMatchWait :: (Ord k, k ~ VarLookupKey subst) => k -> CHRMatcher subst () Source #

data CHRMatchEnv k Source #

Context/environment required for matching itself

Constructors

CHRMatchEnv 

Fields

class (CHREmptySubstitution subst, VarLookupCmb subst subst, VarExtractable x, VarLookupKey subst ~ ExtrValVarKey x) => CHRMatchable env x subst where Source #

A Matchable participates in the reduction process as a reducable constraint. Unification may be incorporated as well, allowing matching to be expressed in terms of unification. This facilitates implementations of CHRBuiltinSolvable.

Methods

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

One-directional (1st to 2nd x) unify

chrUnify :: CHRMatchHow -> CHRMatchEnv (VarLookupKey subst) -> env -> subst -> x -> x -> Maybe subst Source #

One-directional (1st to 2nd x) unify

chrMatchToM :: env -> x -> x -> CHRMatcher subst () Source #

Match one-directional (from 1st to 2nd arg), under a subst, yielding a subst for the metavars in the 1st arg, waiting for those in the 2nd

chrUnifyM :: CHRMatchHow -> env -> x -> x -> CHRMatcher subst () Source #

Unify bi-directional or match one-directional (from 1st to 2nd arg), under a subst, yielding a subst for the metavars in the 1st arg, waiting for those in the 2nd

chrBuiltinSolveM :: env -> x -> CHRMatcher subst () Source #

Solve a constraint which is categorized as ConstraintSolvesVia_Solve

Instances

(Ord (ExtrValVarKey ()), CHREmptySubstitution subst, VarLookupCmb subst subst, (~) * (VarLookupKey subst) (ExtrValVarKey ())) => CHRMatchable env () subst Source # 

Methods

chrMatchTo :: env -> subst -> () -> () -> Maybe subst Source #

chrUnify :: CHRMatchHow -> CHRMatchEnv (VarLookupKey subst) -> env -> subst -> () -> () -> Maybe subst Source #

chrMatchToM :: env -> () -> () -> CHRMatcher subst () Source #

chrUnifyM :: CHRMatchHow -> env -> () -> () -> CHRMatcher subst () Source #

chrBuiltinSolveM :: env -> () -> CHRMatcher subst () Source #

CHRMatchable env x subst => CHRMatchable env [x] subst Source # 

Methods

chrMatchTo :: env -> subst -> [x] -> [x] -> Maybe subst Source #

chrUnify :: CHRMatchHow -> CHRMatchEnv (VarLookupKey subst) -> env -> subst -> [x] -> [x] -> Maybe subst Source #

chrMatchToM :: env -> [x] -> [x] -> CHRMatcher subst () Source #

chrUnifyM :: CHRMatchHow -> env -> [x] -> [x] -> CHRMatcher subst () Source #

chrBuiltinSolveM :: env -> [x] -> CHRMatcher subst () Source #

CHRMatchable env x subst => CHRMatchable env (Maybe x) subst Source # 

Methods

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

chrUnify :: CHRMatchHow -> CHRMatchEnv (VarLookupKey subst) -> env -> subst -> Maybe x -> Maybe x -> Maybe subst Source #

chrMatchToM :: env -> Maybe x -> Maybe x -> CHRMatcher subst () Source #

chrUnifyM :: CHRMatchHow -> env -> Maybe x -> Maybe x -> CHRMatcher subst () Source #

chrBuiltinSolveM :: env -> Maybe x -> CHRMatcher subst () Source #

type family CHRMatchableKey subst :: * Source #

The key of a substitution

data CHRMatchHow Source #

How to match, increasingly more binding is allowed

Constructors

CHRMatchHow_Check

equality check only

CHRMatchHow_Match

also allow one-directional (left to right) matching/binding of (meta)vars

CHRMatchHow_MatchAndWait

also allow giving back of global vars on which we wait

CHRMatchHow_Unify

also allow bi-directional matching, i.e. unification

chrMatchAndWaitToM :: CHRMatchable env x subst => Bool -> env -> x -> x -> CHRMatcher subst () Source #

Match one-directional (from 1st to 2nd arg), under a subst, yielding a subst for the metavars in the 1st arg, waiting for those in the 2nd

class (CHREmptySubstitution subst, VarLookupCmb subst subst) => CHRCheckable env x subst where Source #

A Checkable participates in the reduction process as a guard, to be checked. Checking is allowed to find/return substitutions for meta variables (not for global variables).

Methods

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

chrCheckM :: env -> x -> CHRMatcher subst () Source #

newtype Prio Source #

Separate priority type, where minBound represents lowest prio, and compare sorts from high to low prio (i.e. high compare low == LT)

Constructors

Prio 

Fields

Instances

Bounded Prio Source # 
Enum Prio Source # 

Methods

succ :: Prio -> Prio #

pred :: Prio -> Prio #

toEnum :: Int -> Prio #

fromEnum :: Prio -> Int #

enumFrom :: Prio -> [Prio] #

enumFromThen :: Prio -> Prio -> [Prio] #

enumFromTo :: Prio -> Prio -> [Prio] #

enumFromThenTo :: Prio -> Prio -> Prio -> [Prio] #

Eq Prio Source # 

Methods

(==) :: Prio -> Prio -> Bool #

(/=) :: Prio -> Prio -> Bool #

Integral Prio Source # 

Methods

quot :: Prio -> Prio -> Prio #

rem :: Prio -> Prio -> Prio #

div :: Prio -> Prio -> Prio #

mod :: Prio -> Prio -> Prio #

quotRem :: Prio -> Prio -> (Prio, Prio) #

divMod :: Prio -> Prio -> (Prio, Prio) #

toInteger :: Prio -> Integer #

Num Prio Source # 

Methods

(+) :: Prio -> Prio -> Prio #

(-) :: Prio -> Prio -> Prio #

(*) :: Prio -> Prio -> Prio #

negate :: Prio -> Prio #

abs :: Prio -> Prio #

signum :: Prio -> Prio #

fromInteger :: Integer -> Prio #

Ord Prio Source # 

Methods

compare :: Prio -> Prio -> Ordering #

(<) :: Prio -> Prio -> Bool #

(<=) :: Prio -> Prio -> Bool #

(>) :: Prio -> Prio -> Bool #

(>=) :: Prio -> Prio -> Bool #

max :: Prio -> Prio -> Prio #

min :: Prio -> Prio -> Prio #

Real Prio Source # 

Methods

toRational :: Prio -> Rational #

Show Prio Source # 

Methods

showsPrec :: Int -> Prio -> ShowS #

show :: Prio -> String #

showList :: [Prio] -> ShowS #

PP Prio Source # 

Methods

pp :: Prio -> PP_Doc Source #

ppList :: [Prio] -> PP_Doc Source #

class (Ord (CHRPrioEvaluatableVal x), Bounded (CHRPrioEvaluatableVal x)) => CHRPrioEvaluatable env x subst | x -> env subst where Source #

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

Minimal complete definition

chrPrioLift

Methods

chrPrioEval :: env -> subst -> x -> CHRPrioEvaluatableVal x Source #

Reduce to a prio representation

chrPrioCompare :: env -> (subst, x) -> (subst, x) -> Ordering Source #

Compare priorities

chrPrioLift :: CHRPrioEvaluatableVal x -> x Source #

Lift prio val into prio

type family CHRPrioEvaluatableVal p :: * Source #

The type of value a prio representation evaluates to, must be Ord instance

Orphan instances