| Portability | portable (depends on ghc) |
|---|---|
| Stability | provisional |
| Maintainer | bastiaan.heeren@ou.nl |
| Safe Haskell | None |
Ideas.Service.Types
Description
- 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)
- 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 StrategyConfiguration
- Environment :: Const a Environment
- Text :: Const a Text
- StdGen :: Const a StdGen
- 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 Typed a t | t -> a where
- class Equal f where
- class ShowF f where
- equalM :: Monad m => Type a t1 -> Type a t2 -> m (t1 -> t2)
Services
makeService :: String -> String -> (forall a. TypedValue (Type a)) -> ServiceSource
serviceFunction :: Service -> forall a. TypedValue (Type a)Source
Types
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 |
Constructors
| 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 StrategyConfiguration | |
| Environment :: Const a Environment | |
| Text :: Const a Text | |
| StdGen :: Const a StdGen | |
| SomeExercise :: Const a (Some Exercise) | |
| Bool :: Const a Bool | |
| Int :: Const a Int | |
| String :: Const a String |
data TypedValue f whereSource
Constructors
| ::: :: t -> f t -> TypedValue f |
Instances
| Show (TypedValue (Const a)) | |
| Show (TypedValue f) => Show (TypedValue (TypeRep f)) |
class Typed a t | t -> a whereSource
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) |