THEff-0.1.1.0: TH implementation of effects.

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

Control.THEff.Writer.Strict

Contents

Synopsis

Overview

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

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

import Control.THEff
import Control.THEff.Writer.Strict
import Control.Monad(forM_) 
import Data.Monoid

type IntAccum = Sum Int

mkEff "StrWriter"   ''Writer   ''String    ''NoEff
mkEff "IntWriter"   ''Writer   ''IntAccum  ''StrWriter

main:: IO ()
main = putStrLn $ uncurry (flip (++)) $ runStrWriter $ do
            tell "Result"
            (r, Sum v) <- runIntWriter $ do
                tell "="
                forM_ [1::Int .. 10]
                    (tell . Sum)
                return (pi :: Float)
            return $ show $ r * fromIntegral v

Output : Result=172.7876

Note that for the effect Writer mkEff generates unary function runEEEE. mkEff chooses generation unary or binary function runEEEE based on number of arguments of effect function. E.g. runEffWriter.

Types and functions used in mkEff

data Writer' v e Source

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

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

WriterOuter (o m e) 
WriterAction (Writer' v e) 
WriterResult a 

type WriterResT r v = (r, v) Source

Result type of runEEEE.

effWriter :: EffClass Writer' v e => Writer' 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.

runEffWriter Source

Arguments

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

The outer effect function

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

The chain of effects link wrapper.

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

The chain of effects link unwrapper. -> WriterArgT v -- unused argument!

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

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

Functions that use this effect

tell :: EffClass Writer' v e => v -> Eff e () Source

Add value to monoid.