Copyright | (c) Kolodezny Diver, 2015 |
---|---|
License | GPL-3 |
Maintainer | kolodeznydiver@gmail.com |
Stability | experimental |
Portability | Portable |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
Control.THEff
Description
- mkEff :: String -> Name -> Name -> Name -> DecsQ
- newtype Eff w a = Eff {
- runEff :: (a -> w) -> w
- class EffClass w v e where
- newtype NoEff m a = NoEff {
- unNoEff :: a
- effNoEff :: a -> b
- runNoEff :: Eff (NoEff m a) a -> a
- data Lift' m v = forall a . Lift' (m a) (a -> v)
- class EffClassM m e where
- lift :: (Monad m, EffClassM m e) => m a -> Eff e a
- data Lift m a
- = Lift_ (Lift' m (Lift m a))
- | LiftResult a
- runLift :: Monad m => Eff (Lift m a) a -> m a
Overview
This package implements effects, as alternative to monad transformers. Actually, the effects themselves are created without the use of TH, but the binding of nested effects described by mkEff splice. For example.
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ScopedTypeVariables #-} import Control.THEff import Control.THEff.Reader import Control.THEff.State mkEff "MyReader" ''Reader ''Int ''Lift mkEff "SomeState" ''State ''Bool ''MyReader mkEff "OtherRdr" ''Reader ''Float ''SomeState main:: IO () main = do r <- runMyReader 100 $ runSomeState False $ runOtherRdr pi $ do i :: Int <- ask -- MyReader f :: Float <- ask -- OtherRdr b <- get -- SomeState put $ not b -- SomeState lift $ putStrLn "print from effect!" -- Lift return $ show $ fromIntegral i * f print r
For more information about extensible effects , see the original paper at http://okmij.org/ftp/Haskell/extensible/exteff.pdf. But, this package is significantly different from the original. It uses a chains of ordinary GADTs created by TH. No Typeable, unsafe... , ExistentialQuantification ...
Note. Further, wherever referred to runEEEE is meant mkEff
generated function, e.g.
runMyReader, runSomeState, runOtherRdr .
See more in samples/*.hs
Base THEff support
Arguments
:: String | The name of the new type - the element chain effects. Based on this name mkEff will create new names with prefixes and suffixes. |
-> Name | The type of effect. e.g. |
-> Name | The type used in the first argument runEEEE and / or in
the result of runEEEE. For example, for |
-> Name | The name of previous (outer) element chain effects. |
-> DecsQ |
TH function for building types and functions to ensure the functioning of the chain enclosed in each other's effects
The Monad of effects
class EffClass w v e where Source
Helper class to transfer the action effects by chain.
Instances of this class are created in mkEff
.
Minimal complete definition
No monadic start effect
The first effect in a chain of effects not use monads.
The chain of effects should start or that type, or Lift
(See below.)
This function is used in the mkEff
generated runEEEE... functions.
effNoEff _ = error "THEff: Attempting to call the effect NoEff that does not have any actions!"
runNoEff :: Eff (NoEff m a) a -> a Source
This function is used in the mkEff
generated runEEEE... functions.
Do not use it alone.
Monadic start effect
Helper data type for transfer the monadic action effects by chain.
Constructors
forall a . Lift' (m a) (a -> v) |
class EffClassM m e where Source
Helper class to transfer the monadic action effects by chain.
Instances of this class are created in mkEff
.
Minimal complete definition
The first effect in a chain of monadic effects.
The chain of effects should start or that type, or NoEff
.
Constructors
Lift_ (Lift' m (Lift m a)) | |
LiftResult a |