ideas-1.6: Feedback services for intelligent tutoring systems

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

Ideas.Service.Types

Contents

Description

 

Synopsis

Services

makeService :: String -> String -> (forall a. TypedValue (Type a)) -> Service Source #

Types

data TypeRep f t where Source #

Constructors

Iso :: Isomorphism t1 t2 -> TypeRep f t1 -> TypeRep f t2 
(:->) :: TypeRep f t1 -> TypeRep f t2 -> TypeRep f (t1 -> t2) infixr 3 
IO :: TypeRep f t -> TypeRep f (IO t) 
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) infixr 5 
Unit :: TypeRep f () 
Const :: f t -> TypeRep f t 

Instances

Show (TypedValue f) => Show (TypedValue (TypeRep f)) Source # 
ShowF f => ShowF (TypeRep f) Source # 

Methods

showF :: TypeRep f a -> String Source #

Equal f => Equal (TypeRep f) Source # 

Methods

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

ShowF f => Show (TypeRep f t) Source # 

Methods

showsPrec :: Int -> TypeRep f t -> ShowS #

show :: TypeRep f t -> String #

showList :: [TypeRep f t] -> ShowS #

data Const a t where Source #

Instances

Show (TypedValue (Const a)) Source # 
ShowF (Const a) Source # 

Methods

showF :: Const a a -> String Source #

Equal (Const a) Source # 

Methods

equal :: Const a a -> Const a b -> Maybe (a -> b) Source #

Show (Const a t) Source # 

Methods

showsPrec :: Int -> Const a t -> ShowS #

show :: Const a t -> String #

showList :: [Const a t] -> ShowS #

type Type a = TypeRep (Const a) Source #

data TypedValue f where Source #

Constructors

(:::) :: t -> f t -> TypedValue f infix 2 

class Equal f where Source #

Minimal complete definition

equal

Methods

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

Instances

Equal (Const a) Source # 

Methods

equal :: Const a a -> Const a b -> Maybe (a -> b) Source #

Equal f => Equal (TypeRep f) Source # 

Methods

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

class ShowF f where Source #

Minimal complete definition

showF

Methods

showF :: f a -> String Source #

Instances

ShowF (Const a) Source # 

Methods

showF :: Const a a -> String Source #

ShowF f => ShowF (TypeRep f) Source # 

Methods

showF :: TypeRep f a -> String Source #

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

Constructing types

tUnit :: Type a () Source #

tTuple3 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a (t1, t2, t3) Source #

tTuple4 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a t4 -> Type a (t1, t2, t3, t4) Source #

tTuple5 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a t4 -> Type a t5 -> Type a (t1, t2, t3, t4, t5) Source #

tPair :: Type a t1 -> Type a t2 -> Type a (t1, t2) Source #

tTree :: Type a t -> Type a (Tree t) Source #

tMaybe :: Type a t -> Type a (Maybe t) Source #

tList :: Type a t -> Type a [t] Source #

tDerivation :: Type a t1 -> Type a t2 -> Type a (Derivation t1 t2) Source #

tError :: Type a t -> Type a (Either String t) Source #

(.->) :: Type a t1 -> Type a t2 -> Type a (t1 -> t2) infixr 5 Source #

tIO :: Type a t -> Type a (IO t) Source #

Searching a typed value