effet-0.2.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Cont

Description

The continuation effect, similar to the MonadCont type class from the mtl library.

Synopsis

Tagged Continuation Effect

class Monad m => Cont' tag m where Source #

An effect that adds an abortive continuation to a computation.

Methods

callCC' :: ((a -> m b) -> m a) -> m a Source #

Adapted from the mtl library documentation:

callCC' (call-with-current-continuation) calls a function with the current continuation as its argument. Provides an escape continuation mechanism for use with continuation monads. Escape continuations allow to abort the current computation and return a value immediately. They achieve a similar result to throwError' and catchError' of the Error' effect. Advantage of this function over calling return is that it makes the continuation explicit, allowing more flexibility and better control.

The standard idiom used with callCC' is to provide a lambda-expression to name the continuation. Then calling the named continuation anywhere within its scope will escape from the computation, even if it is many layers deep within nested computations.

Instances

Instances details
Handle (Cont' tag) t m => Cont' (tag :: k) (EachVia (Cont' tag ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Cont

Methods

callCC' :: ((a -> EachVia (Cont' tag ': effs) t m b) -> EachVia (Cont' tag ': effs) t m a) -> EachVia (Cont' tag ': effs) t m a Source #

Find (Cont' tag) effs t m => Cont' (tag :: k) (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Cont

Methods

callCC' :: ((a -> EachVia (other ': effs) t m b) -> EachVia (other ': effs) t m a) -> EachVia (other ': effs) t m a Source #

Cont' (tag :: k1) (ContT r m) Source # 
Instance details

Defined in Control.Effect.Cont

Methods

callCC' :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a Source #

Control (Cont' tag) t m => Cont' (tag :: k) (EachVia ('[] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Cont

Methods

callCC' :: ((a -> EachVia '[] t m b) -> EachVia '[] t m a) -> EachVia '[] t m a Source #

Cont' new m => Cont' (tag :: k2) (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Cont

Methods

callCC' :: ((a -> Tagger tag new m b) -> Tagger tag new m a) -> Tagger tag new m a Source #

Untagged Continuation Effect

If you don't require disambiguation of multiple continuation effects (i.e., you only have one continuation effect in your monadic context), it is recommended to always use the untagged continuation effect.

callCC :: Cont m => ((a -> m b) -> m a) -> m a Source #

Interpretations

runCont' :: forall tag r m a. (a -> m r) -> (Cont' tag `Via` ContT r) m a -> m r Source #

Runs the continuation effect with a given final continuation.

runCont :: (a -> m r) -> (Cont `Via` ContT r) m a -> m r Source #

The untagged version of runCont'.

evalCont' :: forall tag r m. Applicative m => (Cont' tag `Via` ContT r) m r -> m r Source #

Runs the continuation effect with pure as final continuation.

evalCont :: Applicative m => (Cont `Via` ContT r) m r -> m r Source #

The untagged version of evalCont'.

Tagging and Untagging

Conversion functions between the tagged and untagged continuation effect, usually used in combination with type applications, like:

    tagCont' @"newTag" program
    retagCont' @"oldTag" @"newTag" program
    untagCont' @"erasedTag" program

tagCont' :: forall new m a. Via (Cont' G) (Tagger G new) m a -> m a Source #

retagCont' :: forall tag new m a. Via (Cont' tag) (Tagger tag new) m a -> m a Source #

untagCont' :: forall tag m a. Via (Cont' tag) (Tagger tag G) m a -> m a Source #