| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Shift
Synopsis
- module Polysemy.Cont
- data Shift ref s m a where
- trap :: forall ref s a r. Member (Shift ref s) r => (ref a -> Sem r s) -> Sem r a
- invoke :: forall ref s a r. Member (Shift ref s) r => ref a -> a -> Sem r s
- abort :: forall ref s a r. Member (Shift ref s) r => s -> Sem r a
- reset :: forall ref s r. Member (Shift ref s) r => Sem r s -> Sem r s
- reset' :: forall ref s r. Member (Shift ref s) r => Sem r s -> Sem r (Maybe s)
- shift :: Member (Shift ref s) r => ((a -> Sem r s) -> Sem r s) -> Sem r a
- runShiftPure :: Sem '[Shift (Ref (Sem '[]) (Maybe a)) a] a -> Sem '[] (Maybe a)
- runShiftM :: Sem '[Shift (Ref (Sem '[Embed m]) (Maybe a)) a, Embed m] a -> Sem '[Embed m] (Maybe a)
- runShiftFinal :: forall s m a r. (Member (Final (ContT (Maybe s) m)) r, Monad m) => Sem (Shift (Ref m (Maybe s)) s ': r) a -> Sem r a
- runShiftWithCPure :: (a -> Sem '[] (Maybe b)) -> Sem '[Shift (Ref (Sem '[]) (Maybe b)) b] a -> Sem '[] (Maybe b)
- runShiftWithCM :: (a -> Sem '[Embed m] (Maybe b)) -> Sem '[Shift (Ref (Sem '[Embed m]) (Maybe b)) b, Embed m] a -> Sem '[Embed m] (Maybe b)
- runContShiftPure :: Sem [Cont (Ref (Sem '[]) (Maybe a)), Shift (Ref (Sem '[]) (Maybe a)) a] a -> Sem '[] (Maybe a)
- runContShiftM :: Sem [Cont (Ref (Sem '[Embed m]) (Maybe a)), Shift (Ref (Sem '[Embed m]) (Maybe a)) a, Embed m] a -> Sem '[Embed m] (Maybe a)
- runContShiftWithCPure :: (a -> Sem '[] (Maybe s)) -> Sem [Cont (Ref (Sem '[]) (Maybe s)), Shift (Ref (Sem '[]) (Maybe s)) s] a -> Sem '[] (Maybe s)
- runContShiftWithCM :: (a -> Sem '[Embed m] (Maybe s)) -> Sem [Cont (Ref (Sem '[Embed m]) (Maybe s)), Shift (Ref (Sem '[Embed m]) (Maybe s)) s, Embed m] a -> Sem '[Embed m] (Maybe s)
- runShiftUnsafe :: Sem (Shift (Ref (Sem r) (Maybe a)) a ': r) a -> Sem r (Maybe a)
- runShiftWithCUnsafe :: forall s a r. (a -> Sem r (Maybe s)) -> Sem (Shift (Ref (Sem r) (Maybe s)) s ': r) a -> Sem r (Maybe s)
- runContShiftUnsafe :: Sem (Cont (Ref (Sem r) (Maybe a)) ': (Shift (Ref (Sem r) (Maybe a)) a ': r)) a -> Sem r (Maybe a)
- runContShiftWithCUnsafe :: forall s a r. (a -> Sem r (Maybe s)) -> Sem (Cont (Ref (Sem r) (Maybe s)) ': (Shift (Ref (Sem r) (Maybe s)) s ': r)) a -> Sem r (Maybe s)
Documentation
module Polysemy.Cont
Effect
data Shift ref s m a where Source #
An effect for delimited continuations, formulated algebraically through a variant of the 'Polysemy.Cont.Jump/'Polysemy.Cont.Subst' formulation of abortive continuations.
Activating polysemy-plugin is highly recommended when using this effect in order to avoid ambiguous types.
Constructors
| Trap :: (ref a -> m s) -> Shift ref s m a | |
| Invoke :: ref a -> a -> Shift ref s m s | |
| Abort :: s -> Shift ref s m a | |
| Reset :: m s -> Shift ref s m s | |
| Reset' :: m s -> Shift ref s m (Maybe s) | 
Instances
| type DefiningModule Shift Source # | |
| Defined in Polysemy.Shift.Internal | |
Actions
trap :: forall ref s a r. Member (Shift ref s) r => (ref a -> Sem r s) -> Sem r a Source #
Reifies the current continuation in the form of a prompt, and passes it to
 the first argument. Unlike subst, control will never return to the current
 continuation unless the prompt is invoked via release.
invoke :: forall ref s a r. Member (Shift ref s) r => ref a -> a -> Sem r s Source #
Provide an answer to a prompt, jumping to its reified continuation.
 Unlike jump, this will not abort the current continuation, and the
 reified computation will instead return its final result when finished.
Any effectful state of effects which have been run before the interpreter for
 Shift will be embedded in the return value, and therefore the invocation
 won't have any apparent effects unless these are interpreted in the final
 monad.
Any higher-order actions will also not interact with the continuation in any
 meaningful way; i.e. local or censor does
 not affect it, catch will fail to catch any of its exceptions,
 and listen will always return mempty.
The provided continuation may fail locally in its subcontinuations.
 It may sometimes become necessary to handle such cases. To do so,
 use 'reset\'' together with release.
abort :: forall ref s a r. Member (Shift ref s) r => s -> Sem r a Source #
Aborts the current continuation with a result.
reset :: forall ref s r. Member (Shift ref s) r => Sem r s -> Sem r s Source #
Delimits any continuations and calls to abort.
reset' :: forall ref s r. Member (Shift ref s) r => Sem r s -> Sem r (Maybe s) Source #
Delimits any continuations and calls to abort, and detects if
 any subcontinuation has failed locally.
shift :: Member (Shift ref s) r => ((a -> Sem r s) -> Sem r s) -> Sem r a Source #
A variant of callCC.
 Executing the provided continuation will not abort execution.
Any effectful state of effects which have been run before the interpreter for
 Shift will be embedded in the return value of the continuation,
 and therefore the continuation won't have any apparent effects unless these
 effects are interpreted in the final monad.
Any higher-order actions will also not interact with the continuation in any
 meaningful way; i.e. local or censor does
 not affect it, catch will fail to catch any of its exceptions,
 and listen will always return mempty.
The provided continuation may fail locally in its subcontinuations. It may sometimes become necessary to handle such cases, in which case such failure may be detected by using 'reset\'' together with the provided continuation.
Interpretations
runShiftM :: Sem '[Shift (Ref (Sem '[Embed m]) (Maybe a)) a, Embed m] a -> Sem '[Embed m] (Maybe a) Source #
runShiftFinal :: forall s m a r. (Member (Final (ContT (Maybe s) m)) r, Monad m) => Sem (Shift (Ref m (Maybe s)) s ': r) a -> Sem r a Source #
Runs a Shift effect in terms of a final ContT
Beware: Effects that aren't interpreted in terms of the final monad
 will have local state semantics in regards to Shift effects
 interpreted this way. See interpretFinal.
runShiftWithCPure :: (a -> Sem '[] (Maybe b)) -> Sem '[Shift (Ref (Sem '[]) (Maybe b)) b] a -> Sem '[] (Maybe b) Source #
Runs a Shift effect by explicitly providing a final
 continuation.
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runShiftWithCUnsafe, as this may only be used
 as the final interpreter before run.
runShiftWithCM :: (a -> Sem '[Embed m] (Maybe b)) -> Sem '[Shift (Ref (Sem '[Embed m]) (Maybe b)) b, Embed m] a -> Sem '[Embed m] (Maybe b) Source #
Runs a Shift effect by explicitly providing a final
 continuation.
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runShiftWithCUnsafe, as this may only be used
 as the final interpreter before runM.
runContShiftPure :: Sem [Cont (Ref (Sem '[]) (Maybe a)), Shift (Ref (Sem '[]) (Maybe a)) a] a -> Sem '[] (Maybe a) Source #
Runs a Cont and a Shift effect simultaneously by providing
 pure . Just
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runContShiftUnsafe, as this may only be used
 as the final interpreter before run.
runContShiftM :: Sem [Cont (Ref (Sem '[Embed m]) (Maybe a)), Shift (Ref (Sem '[Embed m]) (Maybe a)) a, Embed m] a -> Sem '[Embed m] (Maybe a) Source #
Runs a Cont and a Shift effect simultaneously by providing
 pure . Just
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runContShiftUnsafe, as this may only be used
 as the final interpreter before runM.
runContShiftWithCPure :: (a -> Sem '[] (Maybe s)) -> Sem [Cont (Ref (Sem '[]) (Maybe s)), Shift (Ref (Sem '[]) (Maybe s)) s] a -> Sem '[] (Maybe s) Source #
Runs a Cont and a Shift effect simultaneously by explicitly providing
 a final continuation.
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runContShiftWithCUnsafe, as this may only be
 used as the final interpreter before run.
runContShiftWithCM :: (a -> Sem '[Embed m] (Maybe s)) -> Sem [Cont (Ref (Sem '[Embed m]) (Maybe s)), Shift (Ref (Sem '[Embed m]) (Maybe s)) s, Embed m] a -> Sem '[Embed m] (Maybe s) Source #
Runs a Cont and a Shift effect simultaneously by explicitly providing
 a final continuation.
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
This is a safe variant of runContShiftWithCUnsafe, as this may only be used
 as the final interpreter before runM.
Unsafe Interpretations
runShiftUnsafe :: Sem (Shift (Ref (Sem r) (Maybe a)) a ': r) a -> Sem r (Maybe a) Source #
Runs a Shift effect by providing pure . Just
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
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 runShift after running all interpreters for
 your higher-order effects.__
runShiftWithCUnsafe :: forall s a r. (a -> Sem r (Maybe s)) -> Sem (Shift (Ref (Sem r) (Maybe s)) s ': r) a -> Sem r (Maybe s) Source #
Runs a Shift effect by explicitly providing a final continuation.
The final return type is wrapped in a Maybe due to the fact that any
 continuation may fail locally.
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 runShiftWithC after running all interpreters for
 your higher-order effects.__
runContShiftUnsafe :: Sem (Cont (Ref (Sem r) (Maybe a)) ': (Shift (Ref (Sem r) (Maybe a)) a ': r)) a -> Sem r (Maybe a) Source #
Runs a Cont and a Shift effect simultaneously by providing
 pure . Just
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
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 runShift after running all interpreters for
 your higher-order effects.__
runContShiftWithCUnsafe :: forall s a r. (a -> Sem r (Maybe s)) -> Sem (Cont (Ref (Sem r) (Maybe s)) ': (Shift (Ref (Sem r) (Maybe s)) s ': r)) a -> Sem r (Maybe s) Source #
Runs a Cont and a Shift effect simultaneously by explicitly providing
 a final continuation.
The final return type is wrapped in a Maybe due to the fact that
 any continuation may fail locally.
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 runShift after running all interpreters for
 your higher-order effects.__