uhc-util-0.1.7.0: 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

data ConstraintSolvesVia :: * #

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 #

Minimal complete definition

chrEmptySubst

Methods

chrEmptySubst :: subst #

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

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

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

chrmatcherstateEnv :: Functor f => (c -> f c) -> (a, b, c) -> f (a, b, c) #

chrmatcherstateVarLookup :: Functor f => (a -> f a) -> (a, b, c) -> f (a, b, c) #

chrMatchBind :: (LookupApply subst subst, Lookup subst k v, (~) * k (VarLookupKey subst), (~) * v (VarLookupVal subst)) => k -> v -> CHRMatcher subst () #

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

data CHRMatchEnv k :: * -> * #

Constructors

CHRMatchEnv 

Fields

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

Methods

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

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

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

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

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

Instances

(Ord (ExtrValVarKey ()), CHREmptySubstitution subst, LookupApply subst subst, (~) * (VarLookupKey subst) (ExtrValVarKey ())) => CHRMatchable env () subst 

Methods

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

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

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

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

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

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

Methods

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

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

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

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

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

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

Methods

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

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

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

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

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

type family CHRMatchableKey subst :: * #

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

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

Methods

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

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

newtype Prio :: * #

Constructors

Prio 

Fields

Instances

Bounded Prio 
Enum Prio 

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 

Methods

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

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

Integral Prio 

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 

Methods

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

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

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

negate :: Prio -> Prio #

abs :: Prio -> Prio #

signum :: Prio -> Prio #

fromInteger :: Integer -> Prio #

Ord Prio 

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 

Methods

toRational :: Prio -> Rational #

Show Prio 

Methods

showsPrec :: Int -> Prio -> ShowS #

show :: Prio -> String #

showList :: [Prio] -> ShowS #

PP Prio 

Methods

pp :: Prio -> PP_Doc #

ppList :: [Prio] -> PP_Doc #

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

Minimal complete definition

chrPrioLift

Methods

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

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

chrPrioLift :: CHRPrioEvaluatableVal x -> x #

type family CHRPrioEvaluatableVal p :: * #

Instances

type IVar = Key #