ideas-1.1: Feedback services for intelligent tutoring systems

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

Ideas.Service.Types

Contents

Description

 

Synopsis

Services

Types

data TypeRep f t whereSource

Constructors

Iso :: Isomorphism t1 t2 -> TypeRep f t1 -> TypeRep f t2 
:-> :: TypeRep f t1 -> TypeRep f t2 -> TypeRep f (t1 -> t2) 
Tag :: String -> TypeRep f t1 -> TypeRep f t1 
List :: TypeRep f t -> TypeRep f [t] 
Pair :: TypeRep f t1 -> TypeRep f t2 -> TypeRep f (t1, t2) 
:|: :: TypeRep f t1 -> TypeRep f t2 -> TypeRep f (Either t1 t2) 
Unit :: TypeRep f () 
Const :: f t -> TypeRep f t 

Instances

Show (TypedValue f) => Show (TypedValue (TypeRep f)) 
ShowF f => ShowF (TypeRep f) 
Equal f => Equal (TypeRep f) 
ShowF f => Show (TypeRep f t) 

type Type a = TypeRep (Const a)Source

data TypedValue f whereSource

Constructors

::: :: t -> f t -> TypedValue f 

Instances

class Typed a t | t -> a whereSource

Methods

typeOf :: t -> Type a tSource

typed :: Type a tSource

typedList :: Type a [t]Source

Instances

Typed a Text 
Typed a Script 
Typed a StrategyConfiguration 
Typed a Service 
Typed a Difficulty 
Typed a StdGen 
Typed a Environment 
Typed a Location 
Typed a Id 
Typed a Char 
Typed a () 
Typed a Bool 
Typed a Int 
Typed a DomainReasoner 
Typed a Message 
Typed a (Some Exercise) 
Typed a t => Typed a (Tree t) 
Typed a t => Typed a [t] 
Typed a t => Typed a (Maybe t) 
Typed a (Context a) 
Typed a (Exercise a) 
Typed a (State a) 
Typed a (Strategy (Context a)) 
Typed a (Rule (Context a)) 
Typed a (Diagnosis a) 
Typed a (Result a) 
Typed a (Reply a) 
(Typed a t1, Typed a t2) => Typed a (Derivation t1 t2) 
(Typed a t1, Typed a t2) => Typed a (Either t1 t2) 
(Typed a t1, Typed a t2) => Typed a (t1 -> t2) 
(Typed a t1, Typed a t2) => Typed a (t1, t2) 
(Typed a t1, Typed a t2, Typed a t3) => Typed a (t1, t2, t3) 
(Typed a t1, Typed a t2, Typed a t3, Typed a t4) => Typed a (t1, t2, t3, t4) 

class Equal f whereSource

Methods

equal :: f a -> f b -> Maybe (a -> b)Source

Instances

Equal (Const a) 
Equal f => Equal (TypeRep f) 

class ShowF f whereSource

Methods

showF :: f a -> StringSource

Instances

ShowF (Const a) 
ShowF f => ShowF (TypeRep f) 

equalM :: Monad m => Type a t1 -> Type a t2 -> m (t1 -> t2)Source