THEff-0.1.1.0: TH implementation of effects.

Safe HaskellNone
LanguageHaskell2010
Extensions
  • BangPatterns
  • FlexibleContexts
  • KindSignatures
  • RankNTypes
  • ExplicitForAll

Control.THEff.State.Strict

Contents

Synopsis

Overview

This version builds its output strictly; for a lazy version with the same interface, see Control.THEff.State.

{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}

import Control.THEff
import Control.THEff.State.Strict

mkEff "Example1"   ''State     ''Int      ''NoEff
mkEff "Example2"   ''State     ''Float    ''Example1

main:: IO ()
main = print $ runExample1 123 
             $ runExample2 pi $ do
                    i <- get
                    modify ((1 :: Int) +)
                    put $ i * (2 :: Float)
                    return  $ show i 

Output : (("3.1415927",6.2831855),124)

Types and functions used in mkEff

data State' v e Source

Actually, the effect type - v - Type - the parameter of the effect. - e - mkEff generated type.

data State m e o v a Source

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.

Constructors

StateOuter (o m e) 
StateAction (State' v e) 
StateResult a 

type StateArgT v = v Source

Type of fourth argument of runEffState and first argument of runEEEE.

type StateResT r v = (r, v) Source

Result type of runEEEE.

effState :: EffClass State' v e => State' 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.

runEffState Source

Arguments

:: forall (t :: * -> *) (u :: (* -> *) -> * -> *) (m :: * -> *) (m1 :: * -> *) (o :: (* -> *) -> * -> *). Monad m 
=> (u t r -> (r -> m (StateResT z v)) -> m (StateResT z v))

The outer effect function

-> (State m1 e o w a -> r)

The chain of effects link wrapper.

-> (r -> State t r u v z)

The chain of effects link unwrapper.

-> StateArgT v

The initial value of argument of effect.

-> Eff r a 
-> m (StateResT z v) 

The main function of the effect implementing. This function is used in the mkEff generated runEEEE functions.

Functions that use this effect

get :: EffClass State' v e => Eff e v Source

Get state value

put :: EffClass State' v e => v -> Eff e () Source

Put state value

modify :: EffClass State' v e => (v -> v) -> Eff e () Source

Modify state value

Helper functions

stateOnly Source

Arguments

:: (t -> e -> (r, v))

State effect runEEEE function

-> t

The initial value of argument of effect.

-> e

Eff (MyState m ...) ...

-> v 
 stateOnly runExample1 123 === snd (runExample1 123)

withoutState Source

Arguments

:: (t -> e -> (r, v))

State effect runEEEE function

-> t

The initial value of argument of effect.

-> e

Eff (MyState m ...) ...

-> r 
 withoutState runExample1 123 === fst (runExample1 123)