extensible-effects-5.0.0.1: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Operational

Contents

Description

Operational Monad (https://wiki.haskell.org/Operational) implemented with extensible effects.

Synopsis

Documentation

data Program instr v where Source #

Lift values to an effect. You can think this is a generalization of Lift.

Constructors

Singleton :: instr a -> Program instr a 
Instances
Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source #

Given a continuation and a program, interpret it Usually, we have r ~ [Program f : r']

Instance details

Defined in Control.Eff.Operational

Methods

handle :: (Eff r a -> Intrprtr f r' -> Eff r' a) -> Arrs r v a -> Program f v -> Intrprtr f r' -> Eff r' a Source #

handle_relay :: (r ~ (Program f ': r'0), Relay (Intrprtr f r' -> Eff r' a) r'0) => (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source #

respond_relay :: (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source #

withOperational :: a -> Intrprtr f r -> Eff r a Source #

Embed a pure value

newtype Intrprtr f r Source #

General form of an interpreter

Constructors

Intrprtr 

Fields

Instances
Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source #

Given a continuation and a program, interpret it Usually, we have r ~ [Program f : r']

Instance details

Defined in Control.Eff.Operational

Methods

handle :: (Eff r a -> Intrprtr f r' -> Eff r' a) -> Arrs r v a -> Program f v -> Intrprtr f r' -> Eff r' a Source #

handle_relay :: (r ~ (Program f ': r'0), Relay (Intrprtr f r' -> Eff r' a) r'0) => (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source #

respond_relay :: (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source #

singleton :: Member (Program instr) r => instr a -> Eff r a Source #

Lift a value to a monad.

runProgram :: forall f r a. (forall x. f x -> Eff r x) -> Eff (Program f ': r) a -> Eff r a Source #

Convert values using given interpreter to effects.

Usage

See Control.Eff.Operational.Example for an example of defining data using GADTs and implementing interpreters from the data to effects.

To use the interpreter, see below or consult the tests.

main :: IO ()
main = do
    let comp = runProgram adventPure prog
    putStrLn . fst . run . runMonoidWriter $ evalState comp ["foo","bar"]
    runLift $ runProgram adventIO prog