| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Cont
Synopsis
- data Cont ref m a where
- jump :: forall ref a b r. Member (Cont ref) r => ref a -> a -> Sem r b
- subst :: forall ref a b r. Member (Cont ref) r => (ref a -> Sem r b) -> (a -> Sem r b) -> Sem r b
- callCC :: forall ref a r. Member (Cont ref) r => ((forall b. a -> Sem r b) -> Sem r a) -> Sem r a
- runContPure :: Sem '[Cont (Ref (Sem '[]) a)] a -> Sem '[] a
- runContM :: Sem '[Cont (Ref (Sem '[Embed m]) a), Embed m] a -> Sem '[Embed m] a
- runContFinal :: (Member (Final m) r, MonadCont m) => Sem (Cont (ExitRef m) ': r) a -> Sem r a
- runContUnsafe :: Sem (Cont (Ref (Sem r) a) ': r) a -> Sem r a
- newtype Ref m s a = Ref {- runRef :: a -> m s
 
- newtype ExitRef m a = ExitRef {- enterExit :: forall b. a -> m b
 
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 # | |
| Defined in 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 a r. 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 effectful state back to the point where callCC was invoked,
 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.
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.
runContFinal :: (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 interpretFinal.
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 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.