script-monad-0.0.1: Transformer stack of error, reader, writer, state, and prompt monads

Copyright2018 Automattic Inc.
LicenseBSD3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Script

Contents

Description

Script is an unrolled stack of reader, writer, state, error, and prompt monads, meant as a basis for building more specific DSLs. Also comes in monad transformer flavor with ScriptT.

The addition of prompt to the monad team makes it straightforward to build effectful computations which defer the actual effects (and effect types) to an evaluator function that is both precisely controlled and easily extended. This allows us to build testable and composable API layers.

The name Script is meant to evoke the script of a play. In the theater sense a script is not a list of instructions so much as a list of suggestions, and every cast gives a unique interpretation. Similarly a Script is a pure value that gets an effectful interpretation from a user-supplied evaluator.

Synopsis

Script

type Script e r w s p = ScriptT e r w s p Identity Source #

Opaque stack of error (e), reader (r), writer (w), state (s), and prompt (p) monads.

execScript Source #

Arguments

:: s

Initial state

-> r

Environment

-> (forall u. p u -> u)

Pure evaluator

-> Script e r w s p t 
-> (Either e t, s, w) 

Execute a Script with a specified initial state and environment, and with a pure evaluator.

execScriptM Source #

Arguments

:: Monad eff 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> eff u)

Monadic evaluator

-> Script e r w s p t 
-> eff (Either e t, s, w) 

Execute a Script with a specified inital state and environment, and with a monadic evaluator.

ScriptT

data ScriptT e r w s p m a Source #

Opaque transformer stack of error (e), reader (r), writer (w), state (s), and prompt (p) monads.

Instances

Monoid w => Monad (ScriptT e r w s p m) Source # 

Methods

(>>=) :: ScriptT e r w s p m a -> (a -> ScriptT e r w s p m b) -> ScriptT e r w s p m b #

(>>) :: ScriptT e r w s p m a -> ScriptT e r w s p m b -> ScriptT e r w s p m b #

return :: a -> ScriptT e r w s p m a #

fail :: String -> ScriptT e r w s p m a #

Monoid w => Functor (ScriptT e r w s p m) Source # 

Methods

fmap :: (a -> b) -> ScriptT e r w s p m a -> ScriptT e r w s p m b #

(<$) :: a -> ScriptT e r w s p m b -> ScriptT e r w s p m a #

Monoid w => Applicative (ScriptT e r w s p m) Source # 

Methods

pure :: a -> ScriptT e r w s p m a #

(<*>) :: ScriptT e r w s p m (a -> b) -> ScriptT e r w s p m a -> ScriptT e r w s p m b #

liftA2 :: (a -> b -> c) -> ScriptT e r w s p m a -> ScriptT e r w s p m b -> ScriptT e r w s p m c #

(*>) :: ScriptT e r w s p m a -> ScriptT e r w s p m b -> ScriptT e r w s p m b #

(<*) :: ScriptT e r w s p m a -> ScriptT e r w s p m b -> ScriptT e r w s p m a #

Show (ScriptT e r w s p m a) Source # 

Methods

showsPrec :: Int -> ScriptT e r w s p m a -> ShowS #

show :: ScriptT e r w s p m a -> String #

showList :: [ScriptT e r w s p m a] -> ShowS #

(Monad m, Monoid w, Arbitrary a, CoArbitrary a) => Arbitrary (ScriptT e r w s p m a) Source # 

Methods

arbitrary :: Gen (ScriptT e r w s p m a) #

shrink :: ScriptT e r w s p m a -> [ScriptT e r w s p m a] #

execScriptT Source #

Arguments

:: Monad m 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> u)

Pure effect evaluator

-> ScriptT e r w s p m t 
-> m (Either e t, s, w) 

Execute a ScriptT with a specified initial state and environment, and with a pure evaluator.

execScriptTM Source #

Arguments

:: (Monad (m n), Monad n) 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> n u)

Monadic effect evaluator

-> (forall u. n u -> m n u)

Lift effects to the inner monad

-> ScriptT e r w s p (m n) t 
-> m n (Either e t, s, w) 

Execute a ScriptT with a specified inital state and environment, and with a monadic evaluator. In this case the inner monad m will typically be a monad transformer over the effect monad n.

lift :: (Monoid w, Monad m) => m a -> ScriptT e r w s p m a Source #

Lift a computation in the base monad.

Error

except :: Monoid w => Either e a -> ScriptT e r w s p m a Source #

Inject an Either into a Script.

triage :: Monoid w => (e1 -> e2) -> ScriptT e1 r w s p m a -> ScriptT e2 r w s p m a Source #

Run an action, applying a function to any error.

throw :: Monoid w => e -> ScriptT e r w s p m a Source #

Raise an error.

catch :: ScriptT e r w s p m a -> (e -> ScriptT e r w s p m a) -> ScriptT e r w s p m a Source #

Run an action, applying a handler in case of an error result.

Reader

ask :: Monoid w => ScriptT e r w s p m r Source #

Retrieve the environment.

local :: (r -> r) -> ScriptT e r w s p m a -> ScriptT e r w s p m a Source #

Run an action with a locally adjusted environment of the same type.

transport :: (r2 -> r1) -> ScriptT e r1 w s p m a -> ScriptT e r2 w s p m a Source #

Run an action with a locally adjusted environment of a possibly different type.

reader :: Monoid w => (r -> a) -> ScriptT e r w s p m a Source #

Retrieve the image of the environment under a given function.

Writer

tell :: w -> ScriptT e r w s p m () Source #

Write to the log.

listen :: ScriptT e r w s p m a -> ScriptT e r w s p m (a, w) Source #

Run an action and attach the log to the result.

pass :: ScriptT e r w s p m (a, w -> w) -> ScriptT e r w s p m a Source #

Run an action that returns a value and a log-adjusting function, and apply the function to the local log.

censor :: (w -> w) -> ScriptT e r w s p m a -> ScriptT e r w s p m a Source #

Run an action, applying a function to the local log.

State

get :: Monoid w => ScriptT e r w s p m s Source #

Retrieve the current state.

put :: Monoid w => s -> ScriptT e r w s p m () Source #

Replace the state.

modify :: Monoid w => (s -> s) -> ScriptT e r w s p m () Source #

Modify the current state lazily.

modify' :: Monoid w => (s -> s) -> ScriptT e r w s p m () Source #

Modify the current state strictly.

gets :: Monoid w => (s -> a) -> ScriptT e r w s p m a Source #

Retrieve the image of the current state under a given function.

Prompt

prompt :: Monoid w => p a -> ScriptT e r w s p m a Source #

Inject an atomic effect.

Testing

checkScript Source #

Arguments

:: s

Initial state

-> r

Environment

-> (forall u. p u -> u)

Pure evaluator

-> ((Either e t, s, w) -> q)

Condense

-> (q -> Bool)

Result check

-> Script e r w s p t 
-> Bool 

Turn a Script with a pure evaluator into a Bool; for testing with QuickCheck. Wraps execScript.

checkScriptM Source #

Arguments

:: Monad eff 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> eff u)

Moandic effect evaluator

-> (eff (Either e t, s, w) -> IO q)

Condense to IO

-> (q -> Bool)

Result check

-> Script e r w s p t 
-> Property 

Turn a Script with a monadic evaluator into a Property; for testing with QuickCheck. Wraps execScriptM.

checkScriptT Source #

Arguments

:: Monad m 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> u)

Pure effect evaluator

-> (m (Either e t, s, w) -> IO q)

Condense to IO

-> (q -> Bool)

Result check

-> ScriptT e r w s p m t 
-> Property 

Turn a ScriptT with a pure evaluator into a Property; for testing with QuickCheck. Wraps execScriptT.

checkScriptTM Source #

Arguments

:: (Monad (m eff), Monad eff) 
=> s

Initial state

-> r

Environment

-> (forall u. p u -> eff u)

Moandic effect evaluator

-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

-> (m eff (Either e t, s, w) -> IO q)

Condense to IO

-> (q -> Bool)

Result check

-> ScriptT e r w s p (m eff) t 
-> Property 

Turn a ScriptT with a monadic evaluator into a Property; for testing with QuickCheck. Wraps execScriptTM.