polysemy-zoo-0.7.0.1: Experimental, user-contributed effects and interpreters for polysemy

Safe HaskellTrustworthy
LanguageHaskell2010

Polysemy.Cont

Contents

Synopsis

Effect

data Cont ref m a where Source #

An effect for abortive continuations.

Formulated à la Tom Schrijvers et al. "Monad Transformers and Modular Algebraic Effects: What Binds Them Together" (2016). http://www.cs.kuleuven.be/publicaties/rapporten/cw/CW699.pdf

Activating polysemy-plugin is highly recommended when using this effect in order to avoid ambiguous types.

Constructors

Jump :: ref a -> a -> Cont ref m b 
Subst :: (ref a -> m b) -> (a -> m b) -> Cont ref m b 
Instances
type DefiningModule (Cont :: (Type -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Polysemy.Cont.Internal

type DefiningModule (Cont :: (Type -> Type) -> (k -> Type) -> k -> Type) = "Polysemy.Cont.Internal"

Actions

jump :: forall ref a b r. Member (Cont ref) r => ref a -> a -> Sem r b Source #

Provide an answer to a prompt, jumping to its reified continuation, and aborting the current continuation.

Using jump will rollback all effectful state back to the point where the prompt was created, unless such state is interpreted in terms of the final monad, or the associated interpreter of the effectful state is run after runContUnsafe, which may be done if the effect isn't higher-order.

Higher-order effects do not interact with the continuation in any meaningful way; i.e. local or censor does not affect it, and catch will fail to catch any of its exceptions. The only exception to this is if you interpret such effects and Cont in terms of the final monad, and the final monad can perform such interactions in a meaningful manner.

subst :: forall ref a b r. Member (Cont ref) r => (ref a -> Sem r b) -> (a -> Sem r b) -> Sem r b Source #

Reifies the current continuation in the form of a prompt, and passes it to the first argument. If the prompt becomes invoked via jump, then the second argument will be run before the reified continuation, and otherwise will not be called at all.

callCC :: forall ref r a. Member (Cont ref) r => ((forall b. a -> Sem r b) -> Sem r a) -> Sem r a Source #

Call with current continuation. Executing the provided continuation will abort execution.

Using the provided continuation will rollback all local effectful state back to the point where callCC was invoked.

Higher-order effects do not interact with the continuation in any meaningful way; i.e. local or censor does not affect it, and catch will fail to catch any of its exceptions. The only exception to this is if you interpret such effects and Cont in terms of the final monad, and the final monad can perform such interactions in a meaningful manner.

Interpretations

runContPure :: Sem '[Cont (Ref (Sem '[]) a)] a -> Sem '[] a Source #

Runs a Cont effect by providing pure as the final continuation.

This is a safe variant of runContUnsafe, as this may only be used as the final interpreter before run.

runContM :: Sem '[Cont (Ref (Sem '[Embed m]) a), Embed m] a -> Sem '[Embed m] a Source #

Runs a Cont effect by providing pure as the final continuation.

This is a safe variant of runContUnsafe, as this may only be used as the final interpreter before runM.

contToFinal :: (Member (Final m) r, MonadCont m) => Sem (Cont (ExitRef m) ': r) a -> Sem r a Source #

Runs a Cont effect in terms of a final MonadCont

Beware: Effects that aren't interpreted in terms of the final monad will have local state semantics in regards to Cont effects interpreted this way. See Final.

Experimental Interpretations

runContViaFresh :: forall uniq r a. (Member (Fresh uniq) r, Eq uniq) => Sem (Cont (ViaFreshRef uniq) ': r) a -> Sem r (Maybe a) Source #

A highly experimental Cont interpreter that functions through a combination of Error and Fresh. This may be used safely anywhere in the effect stack.

runContViaFresh is still under development. You're encouraged to experiment with it, but don't rely on it. For best results, use runContViaFresh as the first interpreter you run, such that all other effects are global in respect to it.

This interpreter may return Nothing if the control flow becomes split into separate, inconsistent parts, such that backtracking fails when trying to invoke continuations. For example, if you reify a continuation inside an async:ed thread, and then have that thread return the reified continuation back to the main thread through an await, then runContViaFresh will return Nothing upon executing the continuation in the main thread.

Unsafe Interpretations

runContUnsafe :: Sem (Cont (Ref (Sem r) a) ': r) a -> Sem r a Source #

Runs a Cont effect by providing pure as the final continuation.

Beware: This interpreter will invalidate all higher-order effects of any interpreter run after it; i.e. local and censor will be no-ops, catch will fail to catch exceptions, and listen will always return mempty.

You should therefore use runContUnsafe only after running all interpreters for your higher-order effects.

Note that Final is a higher-order effect, and thus runContUnsafe can't safely be used together with runFinal.

Prompt types

newtype Ref m s a Source #

Constructors

Ref 

Fields

Instances
Contravariant (Ref m s) Source # 
Instance details

Defined in Polysemy.Cont.Internal

Methods

contramap :: (a -> b) -> Ref m s b -> Ref m s a #

(>$) :: b -> Ref m s b -> Ref m s a #

newtype ExitRef m a Source #

Constructors

ExitRef 

Fields

Instances
Contravariant (ExitRef m) Source # 
Instance details

Defined in Polysemy.Cont.Internal

Methods

contramap :: (a -> b) -> ExitRef m b -> ExitRef m a #

(>$) :: b -> ExitRef m b -> ExitRef m a #

data ViaFreshRef uniq a Source #

Instances
Contravariant (ViaFreshRef uniq) Source # 
Instance details

Defined in Polysemy.Cont.Internal

Methods

contramap :: (a -> b) -> ViaFreshRef uniq b -> ViaFreshRef uniq a #

(>$) :: b -> ViaFreshRef uniq b -> ViaFreshRef uniq a #