uhc-util-0.1.6.6: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.CHR.Solve.TreeTrie.Mono

Description

Derived from work by Gerrit vd Geest, but greatly adapted to use more efficient searching.

Assumptions (to be documented further) - The key [Trie.TrieKey Key] used to lookup a constraint in a CHR should be distinguishing enough to be used for the prevention of the application of a propagation rule for a 2nd time.

This is a monomorphic Solver, i.e. the solver is polymorph but therefore can only work on 1 type of constraints, rules, etc.

Synopsis

Documentation

data CHRStore cnstr guard Source

A CHR store is a trie structure

Instances

chrStoreFromElems :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => [Rule c g () ()] -> CHRStore c g Source

Convert from list to store

chrStoreUnion :: Ord (TTKey c) => CHRStore c g -> CHRStore c g -> CHRStore c g Source

chrStoreSingletonElem :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => Rule c g () () -> CHRStore c g Source

chrStoreToList :: Ord (TTKey c) => CHRStore c g -> [(CHRKey c, [Rule c g () ()])] Source

chrStoreElems :: Ord (TTKey c) => CHRStore c g -> [Rule c g () ()] Source

ppCHRStore :: (PP c, PP g, Ord (TTKey c), PP (TTKey c)) => CHRStore c g -> PP_Doc Source

ppCHRStore' :: (PP c, PP g, Ord (TTKey c), PP (TTKey c)) => CHRStore c g -> PP_Doc Source

data SolveStep' c r s Source

A trace step

Constructors

SolveStep 

Fields

stepChr :: r
 
stepSubst :: s
 
stepNewTodo :: [c]
 
stepNewDone :: [c]
 
SolveStats 
SolveDbg 

Fields

stepPP :: PP_Doc
 

Instances

Show (SolveStep' c r s) Source 
(PP r, PP c) => PP (SolveStep' c r s) Source 

type SolveStep c g s = SolveStep' c (Rule c g () ()) s Source

type SolveTrace c g s = SolveTrace' c (Rule c g () ()) s Source

ppSolveTrace :: (PP r, PP c) => SolveTrace' c r s -> PP_Doc Source

type SolveState c g s = SolveState' c (Rule c g () ()) (StoredCHR c g) s Source

emptySolveState :: SolveState' c r sr s Source

solveStateResetDone :: SolveState' c r sr s -> SolveState' c r sr s Source

chrSolveStateDoneConstraints :: SolveState' c r sr s -> [c] Source

chrSolveStateTrace :: SolveState' c r sr s -> SolveTrace' c r s Source

class (IsCHRConstraint env c s, IsCHRGuard env g s, VarLookupCmb s s, VarUpdatable s s, CHREmptySubstitution s, TrTrKey c ~ TTKey c) => IsCHRSolvable env c g s | c g -> s Source

(Class alias) API for solving requirements

chrSolve' :: forall env c g s. IsCHRSolvable env c g s => [CHRTrOpt] -> env -> CHRStore c g -> [c] -> ([c], [c], SolveTrace c g s) Source

Solve

chrSolve'' :: forall env c g s. IsCHRSolvable env c g s => [CHRTrOpt] -> env -> CHRStore c g -> [c] -> SolveState c g s -> SolveState c g s Source

Solve

chrSolveM :: forall env c g s. IsCHRSolvable env c g s => [CHRTrOpt] -> env -> CHRStore c g -> [c] -> State (SolveState c g s) () Source

Solve