Safe Haskell | Unsafe |
---|---|
Language | Haskell2010 |
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
- runContWithCUnsafe :: (a -> Sem r s) -> Sem (Cont (Ref (Sem r) s) ': r) a -> Sem r s
- runContWeaving :: Monad m => (forall x. (x -> m s) -> Sem r x -> m s) -> Weaving (Cont (Ref m s)) (Sem r) a -> ContT s m a
- inspectSem :: Sem r a -> Maybe a
- embedSem :: Union r (Sem r') a -> Sem r (Sem r' a)
- newtype Ref m s a = Ref {
- runRef :: a -> m s
- newtype ExitRef m a = ExitRef {
- enterExit :: forall b. a -> m b
- data ViaFreshRef uniq a = ViaFreshRef {
- getBacktrackException :: a -> (uniq, Any)
- runContViaFreshInC :: forall uniq s r a. (Member (Fresh uniq) r, Eq uniq) => Sem (Cont (ViaFreshRef uniq) ': r) a -> ContT s (Sem (Error (uniq, Any) ': r)) a
- runContViaFreshInCWeave :: forall uniq s r a. (Member (Fresh uniq) r, Eq uniq) => Sem (Cont (ViaFreshRef uniq) ': r) a -> ContT (ContFreshState uniq r s) (Sem (Error (uniq, Any) ': r)) a
- data ContFreshState uniq r a = ResAndHandler {}
Documentation
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.
Instances
type DefiningModule (Cont :: (Type -> Type) -> (k -> Type) -> k -> Type) Source # | |
Defined in Polysemy.Cont.Internal |
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.
runContWithCUnsafe :: (a -> Sem r s) -> Sem (Cont (Ref (Sem r) s) ': r) a -> Sem r s Source #
Runs a Cont
effect by providing a 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 runContWithCUnsafe
after running all interpreters
for your higher-order effects.__
runContWeaving :: Monad m => (forall x. (x -> m s) -> Sem r x -> m s) -> Weaving (Cont (Ref m s)) (Sem r) a -> ContT s m a Source #
inspectSem :: Sem r a -> Maybe a Source #
data ViaFreshRef uniq a Source #
ViaFreshRef | |
|
Instances
Contravariant (ViaFreshRef uniq) Source # | |
Defined in Polysemy.Cont.Internal contramap :: (a -> b) -> ViaFreshRef uniq b -> ViaFreshRef uniq a # (>$) :: b -> ViaFreshRef uniq b -> ViaFreshRef uniq a # |
runContViaFreshInC :: forall uniq s r a. (Member (Fresh uniq) r, Eq uniq) => Sem (Cont (ViaFreshRef uniq) ': r) a -> ContT s (Sem (Error (uniq, Any) ': r)) a Source #
Intermediary monadic interpretation used for running runContViaFresh
.
See source for a discussion on how this works.
runContViaFreshInCWeave :: forall uniq s r a. (Member (Fresh uniq) r, Eq uniq) => Sem (Cont (ViaFreshRef uniq) ': r) a -> ContT (ContFreshState uniq r s) (Sem (Error (uniq, Any) ': r)) a Source #
A variant of runContViaFreshInC
which it uses when weaving other effects through.
data ContFreshState uniq r a Source #
This is the effectful state used by runContViaFreshInC
when weaving through
other effectful actions. The point of it is to avoid delimiting computations
in higher-order effects, by having them return a handler which may be used
to intercept backtrack exceptions of the current continuation.
Instances
Functor (ContFreshState uniq r) Source # | |
Defined in Polysemy.Cont.Internal fmap :: (a -> b) -> ContFreshState uniq r a -> ContFreshState uniq r b # (<$) :: a -> ContFreshState uniq r b -> ContFreshState uniq r a # |