uhc-util-0.1.6.3: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.CHR.Solve.TreeTrie.Poly

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 polymorphic Solver, i.e. the solver is unaware of the type of constraints, rules, etc. because of this type hidden existentially. Tying stuff together is now done by phantom types for environment and substitution, instantiated/relevant only when solving.

Synopsis

Documentation

data CHRStore e s Source

A CHR store is a trie structure

Instances

chrStoreFromElems :: (Ord (TTKey (CHRConstraint e s)), TTKey (CHRConstraint e s) ~ TrTrKey (CHRConstraint e s)) => [CHRRule e s] -> CHRStore e s Source

Convert from list to store

chrStoreToList :: Ord (TTKey (CHRConstraint e s)) => CHRStore e s -> [(CHRKey (CHRConstraint e s), [CHRRule e s])] 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 SolveTrace e s = SolveTrace' (CHRConstraint e s) (CHRRule e s) s Source

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

type SolveState e s = SolveState' (CHRConstraint e s) (CHRRule e s) (StoredCHR e s) 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 (VarLookupCmb s s, VarUpdatable s s, CHREmptySubstitution s, TrTrKey (CHRConstraint e s) ~ TTKey (CHRConstraint e s), CHRMatchableKey s ~ TrTrKey (CHRConstraint e s), PP (CHRMatchableKey s), Ord (CHRMatchableKey s)) => IsCHRSolvable e s Source

(Class alias) API for solving requirements

chrSolve' :: forall e c s. (IsCHRSolvable e s, c ~ CHRConstraint e s) => e -> CHRStore e s -> [c] -> ([c], [c], SolveTrace e s) Source

Solve

chrSolve'' :: forall e c s. (IsCHRSolvable e s, c ~ CHRConstraint e s) => e -> CHRStore e s -> [c] -> SolveState e s -> SolveState e s Source

Solve

chrSolveM :: forall e c s. (IsCHRSolvable e s, c ~ CHRConstraint e s) => e -> CHRStore e s -> [c] -> State (SolveState e s) () Source

Solve