Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
- data Fresh' v e
- data Fresh m e o v a
- = FreshOuter (o m e)
- | FreshAction (Fresh' v e)
- | FreshResult a
- type FreshArgT v = v
- type FreshResT r = r
- effFresh :: EffClass Fresh' v e => Fresh' v r -> Eff e r
- runEffFresh :: forall t u m z v m1 e o w a r. (Monad m, Enum v) => (u t r -> (r -> m (FreshResT z)) -> m (FreshResT z)) -> (Fresh m1 e o w a -> r) -> (r -> Fresh t r u v z) -> FreshArgT v -> Eff r a -> m (FreshResT z)
- fresh :: EffClass Fresh' v e => Eff e v
Overview
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {- # LANGUAGE ScopedTypeVariables #-} module Main where import Control.THEff import Control.THEff.Fresh mkEff "UnicalChar" ''Fresh ''Char ''NoEff main:: IO () main = putStrLn $ runUnicalChar 'A' $ do a <- fresh b <- fresh c <- fresh return $ a:b:[c]
Output : ABC
Types and functions used in mkEff
Actually, the effect type - v - Type - the parameter of the effect. - e - mkEff generated type.
Type implements link in the chain of effects.
Constructors must be named {EffectName}{Outer|WriterAction|WriterResult}
and have a specified types of fields.
- m - Or Monad (if use the Lift
) or phantom type - stub (if used NoEff
).
- o - Type of outer effect.
- a - The result of mkEff generated runEEEE... function.
FreshOuter (o m e) | |
FreshAction (Fresh' v e) | |
FreshResult a |
effFresh :: EffClass Fresh' v e => Fresh' v r -> Eff e r Source
This function is used in the mkEff
generated runEEEE functions and typically
in effect action functions. Calling the effect action.
:: forall (t :: * -> *) (u :: (* -> *) -> * -> *) (m :: * -> *) (m1 :: * -> *) (o :: (* -> *) -> * -> *). (Monad m, Enum v) | |
=> (u t r -> (r -> m (FreshResT z)) -> m (FreshResT z)) | The outer effect function |
-> (Fresh m1 e o w a -> r) | The chain of effects link wrapper. |
-> (r -> Fresh t r u v z) | The chain of effects link unwrapper. |
-> FreshArgT v | The initial value of argument of effect. |
-> Eff r a | |
-> m (FreshResT z) |
The main function of the effect implementing.
This function is used in the mkEff
generated runEEEE functions.