Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
ScriptT
is an unrolled stack of reader, writer, state, error, and prompt monad transformers, meant as a basis for building more specific DSLs. Also comes in "monad transformer transformer" flavor with ScriptTT
.
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 'ScriptT eff a' is a pure value that gets an effectful interpretation in monad eff
from a user-supplied evaluator.
Synopsis
- type ScriptT e r w s p = ScriptTT e r w s p IdentityT
- data ScriptTT (e :: *) (r :: *) (w :: *) (s :: *) (p :: * -> *) (t :: (* -> *) -> * -> *) (eff :: * -> *) (a :: *)
- execScriptTT :: (Monad eff, Monad (t eff), MonadTrans t) => s -> r -> (forall u. p u -> eff u) -> ScriptTT e r w s p t eff a -> t eff (Either e a, s, w)
- liftScriptTT :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => t eff a -> ScriptTT e r w s p t eff a
- except :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => Either e a -> ScriptTT e r w s p t eff a
- triage :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (e1 -> e2) -> ScriptTT e1 r w s p t eff a -> ScriptTT e2 r w s p t eff a
- throw :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => e -> ScriptTT e r w s p t eff a
- catch :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> (e -> ScriptTT e r w s p t eff a) -> ScriptTT e r w s p t eff a
- ask :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff r
- local :: (Monad eff, Monad (t eff), MonadTrans t) => (r -> r) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff a
- transport :: (Monad eff, Monad (t eff), MonadTrans t) => (r2 -> r1) -> ScriptTT e r1 w s p t eff a -> ScriptTT e r2 w s p t eff a
- reader :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t, Monad (t eff)) => (r -> a) -> ScriptTT e r w s p t eff a
- tell :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => w -> ScriptTT e r w s p t eff ()
- draft :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff (a, w)
- listen :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff (a, w)
- pass :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff (a, w -> w) -> ScriptTT e r w s p t eff a
- censor :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (w -> w) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff a
- get :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff s
- put :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => s -> ScriptTT e r w s p t eff ()
- modify :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> s) -> ScriptTT e r w s p t eff ()
- modify' :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> s) -> ScriptTT e r w s p t eff ()
- gets :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> a) -> ScriptTT e r w s p t eff a
- prompt :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => p a -> ScriptTT e r w s p t eff a
- checkScriptTT :: (Monad eff, Monad (t eff), MonadTrans t, Show q) => s -> r -> (forall u. p u -> eff u) -> (t eff (Either e a, s, w) -> IO q) -> (q -> Bool) -> ScriptTT e r w s p t eff a -> Property
ScriptT
type ScriptT e r w s p = ScriptTT e r w s p IdentityT Source #
Opaque stack of error (e
), reader (r
), writer (w
), state (s
), and prompt (p
) monad transformers.
ScriptTT
data ScriptTT (e :: *) (r :: *) (w :: *) (s :: *) (p :: * -> *) (t :: (* -> *) -> * -> *) (eff :: * -> *) (a :: *) Source #
Opaque stack of error (e
), reader (r
), writer (w
), state (s
), and prompt (p
) monad transformers, accepting a monad transformer parameter (t
). Behaves something like a monad transformer transformer.
Instances
(Monoid w, forall (m :: Type -> Type). Monad m => Monad (t m), MonadTrans t) => MonadTrans (ScriptTT e r w s p t) Source # | |
Defined in Control.Monad.Script | |
(Monoid w, Monad eff, Monad (t eff), MonadTrans t) => Monad (ScriptTT e r w s p t eff) Source # | |
Defined in Control.Monad.Script | |
(Monoid w, Monad eff, Monad (t eff), MonadTrans t) => Functor (ScriptTT e r w s p t eff) Source # | |
(Monoid w, Monad eff, Monad (t eff), MonadTrans t) => Applicative (ScriptTT e r w s p t eff) Source # | |
Defined in Control.Monad.Script pure :: a -> ScriptTT e r w s p t eff a # (<*>) :: ScriptTT e r w s p t eff (a -> b) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff b # liftA2 :: (a -> b -> c) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff b -> ScriptTT e r w s p t eff c # (*>) :: ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff b -> ScriptTT e r w s p t eff b # (<*) :: ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff b -> ScriptTT e r w s p t eff a # | |
Show (ScriptTT e r w s p t eff a) Source # | |
(Monoid w, Monad eff, forall (m :: Type -> Type). Monad m => Monad (t m), MonadTrans t, Arbitrary a, CoArbitrary a) => Arbitrary (ScriptTT e r w s p t eff a) Source # | |
:: (Monad eff, Monad (t eff), MonadTrans t) | |
=> s | Initial state |
-> r | Environment |
-> (forall u. p u -> eff u) | Monadic effect evaluator |
-> ScriptTT e r w s p t eff a | |
-> t eff (Either e a, s, w) |
Execute a ScriptTT
with a specified inital state and environment and with a specified prompt evaluator into the effect monad eff
.
liftScriptTT :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => t eff a -> ScriptTT e r w s p t eff a Source #
Lift a value from the inner transformer.
Error
except :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => Either e a -> ScriptTT e r w s p t eff a Source #
Inject an Either
into a Script
.
triage :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (e1 -> e2) -> ScriptTT e1 r w s p t eff a -> ScriptTT e2 r w s p t eff a Source #
Run an action, applying a function to any error.
throw :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => e -> ScriptTT e r w s p t eff a Source #
Raise an error.
catch :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> (e -> ScriptTT e r w s p t eff a) -> ScriptTT e r w s p t eff a Source #
Run an action, applying a handler in case of an error result.
Reader
ask :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff r Source #
Retrieve the environment.
local :: (Monad eff, Monad (t eff), MonadTrans t) => (r -> r) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff a Source #
Run an action with a locally adjusted environment of the same type.
transport :: (Monad eff, Monad (t eff), MonadTrans t) => (r2 -> r1) -> ScriptTT e r1 w s p t eff a -> ScriptTT e r2 w s p t eff a Source #
Run an action with a locally adjusted environment of a possibly different type.
reader :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t, Monad (t eff)) => (r -> a) -> ScriptTT e r w s p t eff a Source #
Retrieve the image of the environment under a given function.
Writer
tell :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => w -> ScriptTT e r w s p t eff () Source #
Write to the log.
draft :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff (a, w) Source #
Run an action and attach the log to the result, setting the log to mempty
.
listen :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff (a, w) Source #
Run an action and attach the log to the result.
pass :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff (a, w -> w) -> ScriptTT e r w s p t eff a Source #
Run an action that returns a value and a log-adjusting function, and apply the function to the local log.
censor :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (w -> w) -> ScriptTT e r w s p t eff a -> ScriptTT e r w s p t eff a Source #
Run an action, applying a function to the local log.
State
get :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => ScriptTT e r w s p t eff s Source #
Retrieve the current state.
put :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => s -> ScriptTT e r w s p t eff () Source #
Replace the state.
modify :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> s) -> ScriptTT e r w s p t eff () Source #
Modify the current state lazily.
modify' :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> s) -> ScriptTT e r w s p t eff () Source #
Modify the current state strictly.
gets :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => (s -> a) -> ScriptTT e r w s p t eff a Source #
Retrieve the image of the current state under a given function.
Prompt
prompt :: (Monoid w, Monad eff, Monad (t eff), MonadTrans t) => p a -> ScriptTT e r w s p t eff a Source #
Inject an atomic effect.
Testing
:: (Monad eff, Monad (t eff), MonadTrans t, Show q) | |
=> s | Initial state |
-> r | Environment |
-> (forall u. p u -> eff u) | Moandic effect evaluator |
-> (t eff (Either e a, s, w) -> IO q) | Condense to |
-> (q -> Bool) | Result check |
-> ScriptTT e r w s p t eff a | |
-> Property |
Turn a ScriptTT
with a monadic evaluator into a Property
; for testing with QuickCheck. Wraps execScriptTT
.