Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | None |
Language | Haskell98 |
- data Service
- makeService :: String -> String -> (forall a. TypedValue (Type a)) -> Service
- deprecate :: Service -> Service
- serviceDeprecated :: Service -> Bool
- serviceFunction :: Service -> forall a. TypedValue (Type a)
- data TypeRep f t where
- Iso :: Isomorphism t1 t2 -> TypeRep f t1 -> TypeRep f t2
- (:->) :: TypeRep f t1 -> TypeRep f t2 -> TypeRep f (t1 -> t2)
- 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)
- Unit :: TypeRep f ()
- Const :: f t -> TypeRep f t
- data Const a t where
- Service :: Const a Service
- Exercise :: Const a (Exercise a)
- Strategy :: Const a (Strategy (Context a))
- State :: Const a (State a)
- Rule :: Const a (Rule (Context a))
- Context :: Const a (Context a)
- Id :: Const a Id
- Location :: Const a Location
- Script :: Const a Script
- StratCfg :: Const a StrategyCfg
- Environment :: Const a Environment
- Text :: Const a Text
- StdGen :: Const a StdGen
- Result :: Const a Result
- SomeExercise :: Const a (Some Exercise)
- Bool :: Const a Bool
- Int :: Const a Int
- String :: Const a String
- type Type a = TypeRep (Const a)
- data TypedValue f where
- (:::) :: t -> f t -> TypedValue f
- class Equal f where
- class ShowF f where
- equalM :: Monad m => Type a t1 -> Type a t2 -> m (t1 -> t2)
- tEnvironment :: Type a Environment
- tLocation :: Type a Location
- tRule :: Type a (Rule (Context a))
- tTuple3 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a (t1, t2, t3)
- tTuple4 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a t4 -> Type a (t1, t2, t3, t4)
- tTuple5 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a t4 -> Type a t5 -> Type a (t1, t2, t3, t4, t5)
- tPair :: Type a t1 -> Type a t2 -> Type a (t1, t2)
- tStrategy :: Type a (Strategy (Context a))
- tTree :: Type a t -> Type a (Tree t)
- tState :: Type a (State a)
- tBool :: Type a Bool
- tMaybe :: Type a t -> Type a (Maybe t)
- tString :: Type a String
- tList :: Type a t -> Type a [t]
- tId :: Type a Id
- tService :: Type a Service
- tSomeExercise :: Type a (Some Exercise)
- tText :: Type a Text
- tDifficulty :: Type a Difficulty
- tContext :: Type a (Context a)
- tDerivation :: Type a t1 -> Type a t2 -> Type a (Derivation t1 t2)
- tError :: Type a t -> Type a (Either String t)
- (.->) :: Type a t1 -> Type a t2 -> Type a (t1 -> t2)
- tIO :: Type a t -> Type a (IO t)
- tExercise :: Type a (Exercise a)
- tTestSuiteResult :: Type a Result
- tStdGen :: Type a StdGen
- tScript :: Type a Script
- tExamples :: Type a (Examples (Context a))
- tStrategyCfg :: Type a StrategyCfg
- tInt :: Type a Int
Services
makeService :: String -> String -> (forall a. TypedValue (Type a)) -> Service Source
serviceDeprecated :: Service -> Bool Source
serviceFunction :: Service -> forall a. TypedValue (Type a) Source
Types
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 |
Service :: Const a Service | |
Exercise :: Const a (Exercise a) | |
Strategy :: Const a (Strategy (Context a)) | |
State :: Const a (State a) | |
Rule :: Const a (Rule (Context a)) | |
Context :: Const a (Context a) | |
Id :: Const a Id | |
Location :: Const a Location | |
Script :: Const a Script | |
StratCfg :: Const a StrategyCfg | |
Environment :: Const a Environment | |
Text :: Const a Text | |
StdGen :: Const a StdGen | |
Result :: Const a Result | |
SomeExercise :: Const a (Some Exercise) | |
Bool :: Const a Bool | |
Int :: Const a Int | |
String :: Const a String |
data TypedValue f where Source
(:::) :: t -> f t -> TypedValue f infix 2 |
Show (TypedValue (Const a)) | |
Show (TypedValue f) => Show (TypedValue (TypeRep f)) |
Constructing types
tTuple5 :: Type a t1 -> Type a t2 -> Type a t3 -> Type a t4 -> Type a t5 -> Type a (t1, t2, t3, t4, t5) Source
tSomeExercise :: Type a (Some Exercise) Source
tDifficulty :: Type a Difficulty Source
tDerivation :: Type a t1 -> Type a t2 -> Type a (Derivation t1 t2) Source
tTestSuiteResult :: Type a Result Source