Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Async m a where
- async :: forall r a. MemberWithError Async r => Sem r a -> Sem r (Async (Maybe a))
- await :: forall r a. MemberWithError Async r => Async a -> Sem r a
- cancel :: forall r a. MemberWithError Async r => Async a -> Sem r ()
- sequenceConcurrently :: forall t r a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a))
- asyncToIO :: Member (Embed IO) r => Sem (Async ': r) a -> Sem r a
- asyncToIOFinal :: Member (Final IO) r => Sem (Async ': r) a -> Sem r a
- lowerAsync :: Member (Embed IO) r => (forall x. Sem r x -> IO x) -> Sem (Async ': r) a -> Sem r a
Effect
An effect for spawning asynchronous computations.
The Maybe
returned by async
is due to the fact that we can't be sure an
Error
effect didn't fail locally.
Since: 0.5.0.0
Async :: m a -> Async m (Async (Maybe a)) | |
Await :: Async a -> Async m a | |
Cancel :: Async a -> Async m () |
Instances
type DefiningModule Async Source # | |
Defined in Polysemy.Async |
Actions
Helpers
sequenceConcurrently :: forall t r a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) Source #
Perform a sequence of effectful actions concurrently.
Since: 1.2.2.0
Interpretations
asyncToIO :: Member (Embed IO) r => Sem (Async ': r) a -> Sem r a Source #
A more flexible --- though less performant ---
version of asyncToIOFinal
.
This function is capable of running Async
effects anywhere within an
effect stack, without relying on Final
to lower it into IO
.
Notably, this means that State
effects will be consistent
in the presence of Async
.
asyncToIO
is unsafe if you're using await
inside higher-order actions
of other effects interpreted after Async
.
See Issue #205.
Prefer asyncToIOFinal
unless you need to run pure, stateful interpreters
after the interpreter for Async
.
(Pure interpreters are interpreters that aren't expressed in terms of
another effect or monad; for example, runState
.)
Since: 1.0.0.0
asyncToIOFinal :: Member (Final IO) r => Sem (Async ': r) a -> Sem r a Source #
Run an Async
effect in terms of async
through final IO
.
Beware: Effects that aren't interpreted in terms of IO
will have local state semantics in regards to Async
effects
interpreted this way. See Final
.
Notably, unlike asyncToIO
, this is not consistent with
State
unless runStateIORef
is used.
State that seems like it should be threaded globally throughout Async
will not be.
Use asyncToIO
instead if you need to run
pure, stateful interpreters after the interpreter for Async
.
(Pure interpreters are interpreters that aren't expressed in terms of
another effect or monad; for example, runState
.)
Since: 1.2.0.0