Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- type Script e r w s p = ScriptT e r w s p Identity
- execScript :: s -> r -> (forall u. p u -> u) -> Script e r w s p t -> (Either e t, s, w)
- execScriptM :: Monad eff => s -> r -> (forall u. p u -> eff u) -> Script e r w s p t -> eff (Either e t, s, w)
- data ScriptT e r w s p m a
- execScriptT :: Monad m => s -> r -> (forall u. p u -> u) -> ScriptT e r w s p m t -> m (Either e t, s, w)
- execScriptTM :: (Monad (m eff), Monad eff) => s -> r -> (forall u. p u -> eff u) -> (forall u. eff u -> m eff u) -> ScriptT e r w s p (m eff) t -> m eff (Either e t, s, w)
- lift :: (Monoid w, Monad m) => m a -> ScriptT e r w s p m a
- except :: Monoid w => Either e a -> ScriptT e r w s p m a
- triage :: Monoid w => (e1 -> e2) -> ScriptT e1 r w s p m a -> ScriptT e2 r w s p m a
- throw :: Monoid w => e -> ScriptT e r w s p m a
- catch :: Monoid w => 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
- ask :: Monoid w => ScriptT e r w s p m r
- local :: (r -> r) -> ScriptT e r w s p m a -> ScriptT e r w s p m a
- transport :: (r2 -> r1) -> ScriptT e r1 w s p m a -> ScriptT e r2 w s p m a
- reader :: Monoid w => (r -> a) -> ScriptT e r w s p m a
- tell :: w -> ScriptT e r w s p m ()
- draft :: Monoid w => ScriptT e r w s p m a -> ScriptT e r w s p m (a, w)
- listen :: ScriptT e r w s p m a -> ScriptT e r w s p m (a, w)
- pass :: ScriptT e r w s p m (a, w -> w) -> ScriptT e r w s p m a
- censor :: (w -> w) -> ScriptT e r w s p m a -> ScriptT e r w s p m a
- get :: Monoid w => ScriptT e r w s p m s
- put :: Monoid w => s -> ScriptT e r w s p m ()
- modify :: Monoid w => (s -> s) -> ScriptT e r w s p m ()
- modify' :: Monoid w => (s -> s) -> ScriptT e r w s p m ()
- gets :: Monoid w => (s -> a) -> ScriptT e r w s p m a
- prompt :: Monoid w => p a -> ScriptT e r w s p m a
- checkScript :: s -> r -> (forall u. p u -> u) -> ((Either e t, s, w) -> q) -> (q -> Bool) -> Script e r w s p t -> Bool
- checkScriptM :: Monad eff => s -> r -> (forall u. p u -> eff u) -> (eff (Either e t, s, w) -> IO q) -> (q -> Bool) -> Script e r w s p t -> Property
- checkScriptT :: Monad m => s -> r -> (forall u. p u -> u) -> (m (Either e t, s, w) -> IO q) -> (q -> Bool) -> ScriptT e r w s p m t -> Property
- checkScriptTM :: (Monad (m eff), Monad eff) => s -> r -> (forall u. p u -> eff u) -> (forall u. eff u -> m eff u) -> (m eff (Either e t, s, w) -> IO q) -> (q -> Bool) -> ScriptT e r w s p (m eff) t -> Property
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.
:: 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.
:: 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 # | |
Monoid w => Functor (ScriptT e r w s p m) Source # | |
Monoid w => Applicative (ScriptT e r w s p m) Source # | |
Defined in Control.Monad.Script 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 # | |
(Monad m, Monoid w, Arbitrary a, CoArbitrary a) => Arbitrary (ScriptT e r w s p m a) Source # | |
:: 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.
:: (Monad (m eff), Monad eff) | |
=> s | Initial state |
-> r | Environment |
-> (forall u. p u -> eff u) | Monadic effect evaluator |
-> (forall u. eff u -> m eff u) | Lift effects to the inner monad |
-> ScriptT e r w s p (m eff) t | |
-> m eff (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
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.
catch :: Monoid w => 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
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
draft :: Monoid w => 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, setting the log to mempty
.
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
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
Testing
:: 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
.
:: 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 |
-> (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
.
:: 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 |
-> (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
.
:: (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 |
-> (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
.