Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class VarUpdatable vv subst where
- class Ord (ExtrValVarKey vv) => VarExtractable vv where
- type family ExtrValVarKey vv :: *
- class VarTerm vv where
Documentation
class VarUpdatable vv subst where Source #
Term in which variables can be updated with a subst(itution)
varUpd :: subst -> vv -> vv infixr 6 Source #
Update
varUpdCyc :: subst -> vv -> (vv, VarMp' (VarLookupKey subst) (VarLookupVal subst)) infixr 6 Source #
Update with cycle detection
Instances
(Ord (VarLookupKey subst), VarUpdatable vv subst) => VarUpdatable [vv] subst Source # | |
Defined in CHR.Data.Substitutable varUpd :: subst -> [vv] -> [vv] Source # varUpdCyc :: subst -> [vv] -> ([vv], VarMp' (VarLookupKey subst) (VarLookupVal subst)) Source # | |
VarUpdatable vv subst => VarUpdatable (Maybe vv) subst Source # | |
Defined in CHR.Data.Substitutable |
class Ord (ExtrValVarKey vv) => VarExtractable vv where Source #
Term from which free variables can be extracted
varFree :: vv -> [ExtrValVarKey vv] Source #
Free vars, as a list
varFreeSet :: vv -> Set (ExtrValVarKey vv) Source #
Free vars, as a set
Instances
(VarExtractable vv, Ord (ExtrValVarKey vv)) => VarExtractable [vv] Source # | |
Defined in CHR.Data.Substitutable varFree :: [vv] -> [ExtrValVarKey [vv]] Source # varFreeSet :: [vv] -> Set (ExtrValVarKey [vv]) Source # | |
(VarExtractable vv, Ord (ExtrValVarKey vv)) => VarExtractable (Maybe vv) Source # | |
Defined in CHR.Data.Substitutable varFree :: Maybe vv -> [ExtrValVarKey (Maybe vv)] Source # varFreeSet :: Maybe vv -> Set (ExtrValVarKey (Maybe vv)) Source # |
type family ExtrValVarKey vv :: * Source #
The variable wich is used as a key into a substitution
Instances
type ExtrValVarKey [vv] Source # | |
Defined in CHR.Data.Substitutable | |
type ExtrValVarKey (Maybe vv) Source # | |
Defined in CHR.Data.Substitutable |
class VarTerm vv where Source #
Term with a (substitutable, extractable, free, etc.) variable
varTermMbKey :: vv -> Maybe (ExtrValVarKey vv) Source #
Maybe is a key
varTermMkKey :: ExtrValVarKey vv -> vv Source #
Construct wrapper for key (i.e. lift, embed)