THEff-0.1.4: TH implementation of effects.

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

Control.THEff.Fresh

Contents

Synopsis

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

data Fresh' v e Source #

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

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

FreshOuter (o m e) 
FreshAction (Fresh' v e) 
FreshResult a 

type FreshArgT v = v Source #

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

type FreshResT r = r Source #

Result type of runEEEE.

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.

runEffFresh Source #

Arguments

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

Functions that use this effect

fresh :: EffClass Fresh' v e => Eff e v Source #

Get a unique value.