minioperational-0.4.9: fast and simple operational monad

Copyright(C) 2012-2013 Fumiaki Kinoshita
LicenseBSD-style (see the file LICENSE)
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Operational.Mini

Description

Simple operational monad

Synopsis

Documentation

newtype Program t a Source

Program t is a Monad that represents a sequence of imperatives. To construct imperatives, use singleton :: t a -> Program t a.

Constructors

Program 

Fields

unProgram :: forall r. (a -> r) -> (forall x. t x -> (x -> r) -> r) -> r
 

Instances

Monad (Program t) 
Functor (Program t) 
Applicative (Program t) 
Tower (Program t) 
type Floors (Program t) = (:) (* -> *) t ((:) (* -> *) (ReifiedProgram t) ((:) (* -> *) Identity ([] (* -> *)))) 

interpret :: Monad m => (forall x. t x -> m x) -> Program t a -> m a Source

Interpret a Program using the given transformation.

cloneProgram :: (Monad m, Elevate t m) => Program t a -> m a Source

data ReifiedProgram t a where Source

Reified version of Program. It is useful for testing.

Constructors

Return :: a -> ReifiedProgram t a 
(:>>=) :: t a -> (a -> ReifiedProgram t b) -> ReifiedProgram t b infixl 1 

Instances

Monad (ReifiedProgram t) 
Functor (ReifiedProgram t) 
Applicative (ReifiedProgram t) 
Tower (ReifiedProgram t) 
type Floors (ReifiedProgram t) = (:) (* -> *) t ((:) (* -> *) (Program t) ((:) (* -> *) Identity ([] (* -> *))))