continue-0.2.0: Monads with suspension and arbitrary-spot reentry

MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellNone

Control.Monad.Continue

Contents

Description

This library implements a monad transformer for suspendable computations, similar and related to free comonads. It allows to write continuation-based web frameworks, command line applications and similar interfaces, where you want to reenter a computation at arbitrary spots.

Synopsis

Documentation

A computation of type ContinueT e f m a is a computation that may either conclude with a value of type a or suspend with a value of type e. Before suspending or concluding it may register a set of reentry spots of type f (ContinueT e f m a). These spots are collected and returned along with the suspension/conclusion value:

 newtype ContinueT e f m a

To run a ContinueT computation you can use the runContinueT function:

 runContinueT :: ContinueT e f m a
              -> m (Either e a, f (ContinueT e f m a))

The result is either a suspension value of type e or a conclusion of type a. In both cases you can reenter the computation at the registered spots. Example:

 type MyMonad = ContinueT () (Map String) Identity

 myComp :: MyMonad Integer
 myComp = do
     x <- continue (Right 3) (M.singleton "x" (Right 15))
     y <- continue (Right 4) (M.singleton "y" (Right 17))
     return (x + y)

When you first run this computation the result will be the conclusion 3 + 4. Since MyMonad transforms to Identity we can use the convenience type alias Continue and the function runContinue:

 type MyMonad = Continue () (Map String)

 runContinue myComp
 = (Right 7, reentryMap)

Along with the result you will also get a reentry map of type Map String (MyMonad Integer). If you run the computation indexed by "x", you will get the result 15 + 4. This iteration itself will return a new reentry map on its part. That map will contain only the reentry spot "y", because the reentry indexed by "x" does not register itself again.

You can use the more general addCont function to register arbitrary reentry spots, which themselves are allowed to register new spots. Also In some kinds of applications you would want to combine the reentry maps produced. You can use the <!> function to do that:

 let overallReentryMap = reentryMap1 <!> reentryMap2

Since e is required to be a monoid, ContinueT forms a family of alternative functors that implement choice based on suspension and conclusion. The computation empty always suspends with mempty.

 x <|> y

This computation concludes with the conclusion of either x or y trying them in that order, or suspends if both of them suspend. Note that both computations are performed to their conclusion or suspension. This allows y both to have monadic effects as well as to register reentry points, even if x concludes.

There is also a combinator orElse that tries y only if x actually suspends. In that case, if x concludes, then y cannot register reentry spots or have effects in the underlying monad.

Continue

runContinue :: Continue e f a -> (Either e a, f (Continue e f a))Source

Run the given Continue computation.

ContinueT

newtype ContinueT e f m a Source

This monad transformer adds continuations under f and e-typed suspensions to m.

Constructors

ContinueT 

Fields

runContinueT :: m (Either e a, f (ContinueT e f m a))
 

Instances

(Monad m, Monoid e, Plus f) => MonadContinue e f (ContinueT e f m) 
(MonadBase b m, Monoid e, Plus f) => MonadBase b (ContinueT e f m) 
(MonadBaseControl b m, Monoid e, Plus f) => MonadBaseControl b (ContinueT e f m) 
(Monad m, Monoid e, Plus f) => MonadError e (ContinueT e f m) 
(MonadReader r m, Monoid e, Plus f) => MonadReader r (ContinueT e f m) 
(MonadState s m, Monoid e, Plus f) => MonadState s (ContinueT e f m) 
(MonadWriter l m, Monoid e, Plus f) => MonadWriter l (ContinueT e f m) 
Plus f => MonadTrans (ContinueT e f) 
(Monad m, Monoid e, Plus f) => Monad (ContinueT e f m) 
(Functor f, Monad m) => Functor (ContinueT e f m) 
(MonadFix m, Monoid e, Plus f) => MonadFix (ContinueT e f m)

Warning: If feedback is broken by suspension you get a run-time error.

(Monad m, Monoid e, Plus f) => MonadPlus (ContinueT e f m) 
(Monad m, Plus f) => Applicative (ContinueT e f m) 
(Monad m, Monoid e, Plus f) => Alternative (ContinueT e f m) 
(MonadIO m, Monoid e, Plus f) => MonadIO (ContinueT e f m) 

mapContinueTSource

Arguments

:: (Functor f, Monad n) 
=> (forall a. m a -> n a)

Monad morphism to apply.

-> ContinueT e f m a 
-> ContinueT e f n a 

Apply the given morphism to the underlying monad.

Combinators

orElse :: (Alt f, Monad m, Monoid e) => ContinueT e f m a -> ContinueT e f m a -> ContinueT e f m aSource

Similar to <|>, but tries the second computation only if the first one actually suspends. Note that not running the second computation also means that it can't register reentry spots.

As an operator this function is infixr 3.

Convenience types

type LastEx = Last SomeExceptionSource

Type alias for the common case of using Last SomeException as the suspension monoid.

Reexports

class Functor f => Alt f where

Laws:

 <!> is associative:             (a <!> b) <!> c = a <!> (b <!> c)
 <$> left-distributes over <!>:  f <$> (a <!> b) = (f <$> a) <!> (f <$> b)

If extended to an Alternative then <!> should equal <|>.

Ideally, an instance of Alt also satisfies the "left distributon" law of MonadPlus with respect to .:

 <.> right-distributes over <!>: (a <!> b) <.> c = (a <.> c) <!> (b <.> c)

But Maybe, IO, Either a, ErrorT e m, and STM satisfy the alternative "left catch" law instead:

 pure a <!> b = pure a

However, this variation cannot be stated purely in terms of the dependencies of Alt.

When and if MonadPlus is successfully refactored, this class should also be refactored to remove these instances.

The right distributive law should extend in the cases where the a Bind or Monad is provided to yield variations of the right distributive law:

 (m <!> n) >>- f = (m >>- f) <!> (m >>- f)
 (m <!> n) >>= f = (m >>= f) <!> (m >>= f)

Methods

(<!>) :: f a -> f a -> f a

(|) without a required empty

some :: Applicative f => f a -> f [a]

many :: Applicative f => f a -> f [a]

Instances

Alt [] 
Alt IO

This instance does not actually satisfy the (.) right distributive law It instead satisfies the Left-Catch law

Alt Maybe 
Alt Seq 
Alt IntMap 
Alt Option 
Alt NonEmpty 
Alt (Either a) 
MonadPlus m => Alt (WrappedMonad m) 
Ord k => Alt (Map k) 
Apply f => Alt (ListT f) 
Alternative f => Alt (WrappedApplicative f) 
(Bind f, Monad f) => Alt (MaybeT f) 
Alt f => Alt (IdentityT f) 
ArrowPlus a => Alt (WrappedArrow a b) 
(Bind f, Monad f) => Alt (ErrorT e f) 
Alt f => Alt (ReaderT e f) 
Alt f => Alt (StateT e f) 
Alt f => Alt (StateT e f) 
Alt f => Alt (WriterT w f) 
Alt f => Alt (WriterT w f) 
Alt f => Alt (RWST r w s f) 
Alt f => Alt (RWST r w s f) 

class Alt f => Plus f where

Laws:

 zero <!> m = m
 m <!> zero = m

If extended to an Alternative then zero should equal empty.

Methods

zero :: f a

Instances

Plus [] 
Plus IO 
Plus Maybe 
Plus Seq 
Plus IntMap 
Plus Option 
MonadPlus m => Plus (WrappedMonad m) 
Ord k => Plus (Map k) 
(Apply f, Applicative f) => Plus (ListT f) 
Alternative f => Plus (WrappedApplicative f) 
(Bind f, Monad f) => Plus (MaybeT f) 
Plus f => Plus (IdentityT f) 
ArrowPlus a => Plus (WrappedArrow a b) 
(Bind f, Monad f, Error e) => Plus (ErrorT e f) 
Plus f => Plus (ReaderT e f) 
Plus f => Plus (StateT e f) 
Plus f => Plus (StateT e f) 
Plus f => Plus (WriterT w f) 
Plus f => Plus (WriterT w f) 
Plus f => Plus (RWST r w s f) 
Plus f => Plus (RWST r w s f)