chr-data-0.1.0.1: Datatypes required for chr library

Safe HaskellNone
LanguageHaskell2010

CHR.Data.Substitutable

Synopsis

Documentation

class VarUpdatable vv subst where Source #

Term in which variables can be updated with a subst(itution)

Minimal complete definition

varUpd

Methods

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 # 
Instance details

Defined in CHR.Data.Substitutable

Methods

varUpd :: subst -> [vv] -> [vv] Source #

varUpdCyc :: subst -> [vv] -> ([vv], VarMp' (VarLookupKey subst) (VarLookupVal subst)) Source #

VarUpdatable vv subst => VarUpdatable (Maybe vv) subst Source # 
Instance details

Defined in CHR.Data.Substitutable

Methods

varUpd :: subst -> Maybe vv -> Maybe vv Source #

varUpdCyc :: subst -> Maybe vv -> (Maybe vv, VarMp' (VarLookupKey subst) (VarLookupVal subst)) Source #

class Ord (ExtrValVarKey vv) => VarExtractable vv where Source #

Term from which free variables can be extracted

Methods

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 # 
Instance details

Defined in CHR.Data.Substitutable

Methods

varFree :: [vv] -> [ExtrValVarKey [vv]] Source #

varFreeSet :: [vv] -> Set (ExtrValVarKey [vv]) Source #

(VarExtractable vv, Ord (ExtrValVarKey vv)) => VarExtractable (Maybe vv) Source # 
Instance details

Defined in CHR.Data.Substitutable

type family ExtrValVarKey vv :: * Source #

The variable wich is used as a key into a substitution

Instances
type ExtrValVarKey [vv] Source # 
Instance details

Defined in CHR.Data.Substitutable

type ExtrValVarKey (Maybe vv) Source # 
Instance details

Defined in CHR.Data.Substitutable

class VarTerm vv where Source #

Term with a (substitutable, extractable, free, etc.) variable

Minimal complete definition

varTermMbKey, varTermMkKey

Methods

varTermMbKey :: vv -> Maybe (ExtrValVarKey vv) Source #

Maybe is a key

varTermMkKey :: ExtrValVarKey vv -> vv Source #

Construct wrapper for key (i.e. lift, embed)