Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- data Capture ref m a where
- reify :: forall ref a r. Member (Capture ref) r => (forall s. ref s a -> Sem r s) -> Sem r a
- reflect :: forall ref s a r. Member (Capture ref) r => ref s a -> a -> Sem r s
- delimit :: forall ref a r. Member (Capture ref) r => Sem r a -> Sem r a
- delimit' :: forall ref a r. Member (Capture ref) r => Sem r a -> Sem r (Maybe a)
- capture :: forall ref r a. Member (Capture ref) r => (forall s. (a -> Sem r s) -> Sem r s) -> Sem r a
- runCapture :: Sem (Capture (Ref (Sem r)) ': r) a -> Sem r (Maybe a)
- runCaptureWithC :: (a -> Sem r (Maybe s)) -> Sem (Capture (Ref (Sem r)) ': r) a -> Sem r (Maybe s)
- newtype Ref m s a = Ref {
- runRef :: a -> m s
Effect
data Capture ref m a where Source #
A less powerful variant of Shift
that may always be
interpreted safely. Unlike Shift
,
continuations can't leave the scope in which they are provided.
Note: Any computation used in a higher-order effect will be delimited.
Activating polysemy-plugin is highly recommended when using this effect in order to avoid ambiguous types.
Reify :: (forall s. ref s a -> m s) -> Capture ref m a | |
Reflect :: ref s a -> a -> Capture ref m s | |
Delimit :: m a -> Capture ref m a | |
Delimit' :: m a -> Capture ref m (Maybe a) |
Instances
type DefiningModule Capture Source # | |
Defined in Polysemy.Capture |
Actions
reify :: forall ref a r. Member (Capture ref) r => (forall s. ref s 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.
reflect :: forall ref s a r. Member (Capture ref) r => ref s a -> a -> Sem r s Source #
Provide an answer to a prompt, jumping to its reified continuation. This will not abort the current continuation, and the reified computation will return its final result when finished.
The provided continuation may fail locally in its subcontinuations.
It may sometimes become necessary to handle such cases. To do so,
use delimit'
together with reflect
(the reified continuation
is already delimited).
delimit :: forall ref a r. Member (Capture ref) r => Sem r a -> Sem r a Source #
Delimits any continuations
delimit' :: forall ref a r. Member (Capture ref) r => Sem r a -> Sem r (Maybe a) Source #
Delimits any continuations, and detects if any subcontinuation has failed locally.
capture :: forall ref r a. Member (Capture ref) r => (forall s. (a -> Sem r s) -> Sem r s) -> Sem r a Source #
A restricted version of shift
.
Executing the provided continuation will not abort execution.
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 delimit'
together
with the provided continuation (the provided continuation
is already delimited).
Interpretations
runCaptureWithC :: (a -> Sem r (Maybe s)) -> Sem (Capture (Ref (Sem r)) ': r) a -> Sem r (Maybe s) Source #