THEff-0.1.4: TH implementation of effects.

Copyright(c) Kolodezny Diver 2015
LicenseGPL-3
Maintainerkolodeznydiver@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • GADTs
  • GADTSyntax
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • KindSignatures
  • RankNTypes
  • ExplicitForAll

Control.THEff

Contents

Description

 

Synopsis

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

mkEff Source #

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. State or Reader.

-> Name

The type used in the first argument runEEEE and / or in the result of runEEEE. For example, for State effect, of items this type used in get, put, modify.

-> 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

newtype Eff w a Source #

The Monad of effects

Constructors

Eff 

Fields

Instances

Monad (Eff w) Source # 

Methods

(>>=) :: Eff w a -> (a -> Eff w b) -> Eff w b #

(>>) :: Eff w a -> Eff w b -> Eff w b #

return :: a -> Eff w a #

fail :: String -> Eff w a #

Functor (Eff w) Source # 

Methods

fmap :: (a -> b) -> Eff w a -> Eff w b #

(<$) :: a -> Eff w b -> Eff w a #

Applicative (Eff w) Source # 

Methods

pure :: a -> Eff w a #

(<*>) :: Eff w (a -> b) -> Eff w a -> Eff w b #

(*>) :: Eff w a -> Eff w b -> Eff w b #

(<*) :: Eff w a -> Eff w b -> Eff w a #

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

toEff

Methods

effAction :: ((r -> e) -> w v e) -> Eff e r Source #

toEff :: w v e -> e Source #

No monadic start effect

newtype NoEff m a Source #

The first effect in a chain of effects not use monads. The chain of effects should start or that type, or Lift (See below.)

Constructors

NoEff 

Fields

effNoEff :: a -> b Source #

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

data Lift' m v Source #

Helper data type for transfer the monadic action effects by chain.

Constructors

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

toEffM

Methods

effLift :: Lift' m r -> Eff e r Source #

toEffM :: Lift' m e -> e Source #

Instances

EffClassM m (Lift m a) Source # 

Methods

effLift :: Lift' m r -> Eff (Lift m a) r Source #

toEffM :: Lift' m (Lift m a) -> Lift m a Source #

lift :: EffClassM m e => m a -> Eff e a Source #

Lift a Monad to an Effect.

data Lift m a Source #

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 

Instances

EffClassM m (Lift m a) Source # 

Methods

effLift :: Lift' m r -> Eff (Lift m a) r Source #

toEffM :: Lift' m (Lift m a) -> Lift m a Source #

runLift :: Monad m => Eff (Lift m a) a -> m a Source #

This function is used in the mkEff generated runEEEE... functions. Do not use it alone.