ideas-1.8: Feedback services for intelligent tutoring systems

Maintainerbastiaan.heeren@ou.nl
Stabilityprovisional
Portabilityportable (depends on ghc)
Safe HaskellNone
LanguageHaskell98

Ideas.Common.Environment

Contents

Description

References, bindings, and heterogenous environments

Synopsis

Reference

data Ref a Source #

A data type for references (without a value)

Instances
HasTypeable Ref Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

getTypeable :: Ref a -> Maybe (IsTypeable a) Source #

Eq (Ref a) Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

(==) :: Ref a -> Ref a -> Bool #

(/=) :: Ref a -> Ref a -> Bool #

Show (Ref a) Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

showsPrec :: Int -> Ref a -> ShowS #

show :: Ref a -> String #

showList :: [Ref a] -> ShowS #

HasId (Ref a) Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

getId :: Ref a -> Id Source #

changeId :: (Id -> Id) -> Ref a -> Ref a Source #

class (IsTerm a, Typeable a, Show a, Read a) => Reference a where Source #

A type class for types as references

Methods

makeRef :: IsId n => n -> Ref a Source #

makeRefList :: IsId n => n -> Ref [a] Source #

Instances
Reference Char Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref Char Source #

makeRefList :: IsId n => n -> Ref [Char] Source #

Reference Int Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref Int Source #

makeRefList :: IsId n => n -> Ref [Int] Source #

Reference ShowString Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref ShowString Source #

makeRefList :: IsId n => n -> Ref [ShowString] Source #

Reference Term Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref Term Source #

makeRefList :: IsId n => n -> Ref [Term] Source #

Reference a => Reference [a] Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref [a] Source #

makeRefList :: IsId n => n -> Ref [[a]] Source #

(Reference a, Reference b) => Reference (a, b) Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

makeRef :: IsId n => n -> Ref (a, b) Source #

makeRefList :: IsId n => n -> Ref [(a, b)] Source #

mapRef :: Typeable b => Isomorphism a b -> Ref a -> Ref b Source #

Binding

data Binding Source #

Instances
Eq Binding Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

(==) :: Binding -> Binding -> Bool #

(/=) :: Binding -> Binding -> Bool #

Show Binding Source # 
Instance details

Defined in Ideas.Common.Environment

HasId Binding Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

getId :: Binding -> Id Source #

changeId :: (Id -> Id) -> Binding -> Binding Source #

Heterogeneous environment

class HasEnvironment env where Source #

Minimal complete definition

environment, setEnvironment

Methods

environment :: env -> Environment Source #

setEnvironment :: Environment -> env -> env Source #

deleteRef :: Ref a -> env -> env Source #

insertRef :: Ref a -> a -> env -> env Source #

changeRef :: Ref a -> (a -> a) -> env -> env Source #

class HasRefs a where Source #

Minimal complete definition

allRefs

Methods

getRefs :: a -> [Some Ref] Source #

allRefs :: a -> [Some Ref] Source #

getRefIds :: a -> [Id] Source #

Instances
HasRefs Environment Source # 
Instance details

Defined in Ideas.Common.Environment

HasRefs (Recognizer a) Source # 
Instance details

Defined in Ideas.Common.Rule.Recognizer

HasRefs (Rule a) Source # 
Instance details

Defined in Ideas.Common.Rule.Abstract

Methods

getRefs :: Rule a -> [Some Ref] Source #

allRefs :: Rule a -> [Some Ref] Source #

getRefIds :: Rule a -> [Id] Source #

HasRefs (Trans a b) Source # 
Instance details

Defined in Ideas.Common.Rule.Transformation

Methods

getRefs :: Trans a b -> [Some Ref] Source #

allRefs :: Trans a b -> [Some Ref] Source #

getRefIds :: Trans a b -> [Id] Source #

(?) :: HasEnvironment env => Ref a -> env -> Maybe a Source #