Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- data CHRStore cnstr guard
- emptyCHRStore :: CHRStore cnstr guard
- data StoredCHR c g = StoredCHR {
- storedChr :: !(Rule c g () ())
- storedKeyedInx :: !Int
- storedKeys :: ![Maybe (CHRKey c)]
- storedIdent :: !(UsedByKey c)
- chrStoreFromElems :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => [Rule c g () ()] -> CHRStore c g
- chrStoreUnion :: Ord (TTKey c) => CHRStore c g -> CHRStore c g -> CHRStore c g
- chrStoreUnions :: Ord (TTKey c) => [CHRStore c g] -> CHRStore c g
- chrStoreSingletonElem :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => Rule c g () () -> CHRStore c g
- chrStoreToList :: Ord (TTKey c) => CHRStore c g -> [(CHRKey c, [Rule c g () ()])]
- chrStoreElems :: Ord (TTKey c) => CHRStore c g -> [Rule c g () ()]
- ppCHRStore :: (PP c, PP g, Ord (TTKey c), PP (TTKey c)) => CHRStore c g -> PP_Doc
- ppCHRStore' :: (PP c, PP g, Ord (TTKey c), PP (TTKey c)) => CHRStore c g -> PP_Doc
- data SolveStep' c r s
- = SolveStep {
- stepChr :: r
- stepSubst :: s
- stepAlt :: Maybe [c]
- stepNewTodo :: [c]
- stepNewDone :: [c]
- | SolveStats { }
- | SolveDbg { }
- = SolveStep {
- type SolveStep c g s = SolveStep' c (Rule c g () ()) s
- type SolveTrace c g s = SolveTrace' c (Rule c g () ()) s
- ppSolveTrace :: (PP r, PP c) => SolveTrace' c r s -> PP_Doc
- type SolveState c g s = SolveState' c (Rule c g () ()) (StoredCHR c g) s
- emptySolveState :: SolveState' c r sr s
- solveStateResetDone :: SolveState' c r sr s -> SolveState' c r sr s
- chrSolveStateDoneConstraints :: SolveState' c r sr s -> [c]
- chrSolveStateTrace :: SolveState' c r sr s -> SolveTrace' c r s
- class (IsCHRConstraint env c s, IsCHRGuard env g s, LookupApply s s, CHREmptySubstitution s, TrTrKey c ~ TTKey c) => IsCHRSolvable env c g s | c g -> s
- chrSolve' :: forall env c g s. IsCHRSolvable env c g s => [CHRTrOpt] -> env -> CHRStore c g -> [c] -> ([c], [c], SolveTrace c g s)
- 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
- chrSolveM :: forall env c g s. IsCHRSolvable env c g s => [CHRTrOpt] -> env -> CHRStore c g -> [c] -> State (SolveState c g s) ()
Documentation
emptyCHRStore :: CHRStore cnstr guard Source #
A CHR as stored in a CHRStore, requiring additional info for efficiency
StoredCHR | |
|
chrStoreFromElems :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => [Rule c g () ()] -> CHRStore c g Source #
Convert from list to store
chrStoreSingletonElem :: (TTKeyable c, Ord (TTKey c), TTKey c ~ TrTrKey c) => Rule c g () () -> CHRStore c g Source #
data SolveStep' c r s Source #
A trace step
SolveStep | |
| |
SolveStats | |
SolveDbg | |
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 #
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, LookupApply 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