Copyright | (c) 2024-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Concurrent.Parallel
Description
Effects for parallel computations.
Synopsis
- data Parallel (a :: Type -> Type) b where
- data Halt (a :: Type -> Type) b where
- data Race (a :: Type -> Type) b where
- data HaltLabel
- halt :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Halt :> es) => f a
- halt' :: forall {k} (key :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Halt es) => f a
- halt'' :: forall {k} (tag :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Halt :> es) => f a
- halt'_ :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Halt es) => f a
- data RaceLabel
- data ParallelLabel
- liftP2 :: forall a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Parallel :> es) => (a -> b -> c1) -> f a -> f b -> f c1
- liftP2' :: forall {k} (key :: k) a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Has key Parallel es) => (a -> b -> c1) -> f a -> f b -> f c1
- liftP2'' :: forall {k} (tag :: k) a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Tagged tag Parallel :> es) => (a -> b -> c1) -> f a -> f b -> f c1
- liftP2'_ :: forall a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, In Parallel es) => (a -> b -> c1) -> f a -> f b -> f c1
- race :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Race :> es) => f a -> f a -> f a
- race' :: forall {k} (key :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Race es) => f a -> f a -> f a
- race'' :: forall {k} (tag :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Race :> es) => f a -> f a -> f a
- race'_ :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Race es) => f a -> f a -> f a
- newtype Concurrently (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a = Concurrently {
- runConcurrently :: Eff ff es a
- liftP3 :: forall a b c d (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (con :: (Type -> Type) -> Constraint). (Parallel :> es, Free con ff) => (a -> b -> c -> d) -> Eff ff es a -> Eff ff es b -> Eff ff es c -> Eff ff es d
- data Poll (a :: Type -> Type) b where
- data PollLabel
- poldl :: forall a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Poll :> es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- poldl' :: forall {k} (key :: k) a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Poll es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- poldl'' :: forall {k} (tag :: k) a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Poll :> es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- poldl'_ :: forall a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Poll es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- cancels :: forall a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Poll :> es, Applicative (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es b -> Eff ff es (a, Maybe b)
- cancelBy :: forall a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Poll :> es, Applicative (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es b -> Eff ff es (Maybe a, b)
- data For (t :: Type -> Type) (a :: Type -> Type) b where
- data ForLabel
- for :: forall t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, For t :> es) => t (f a) -> f (t a)
- for' :: forall {k} (key :: k) t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (For t) es) => t (f a) -> f (t a)
- for'' :: forall {k} (tag :: k) t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (For t) :> es) => t (f a) -> f (t a)
- for'_ :: forall t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (For t) es) => t (f a) -> f (t a)
- forToParallel :: forall (t :: Type -> Type) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Parallel :> es, Traversable t, Applicative (Eff ff es), Free c ff) => For t (Eff ff es) a -> Eff ff es a
- runConcurrentIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, forall (es' :: [Effect]). Monad (Eff ff es'), Free c ff) => Eff ff (Parallel ': (Race ': (Poll ': (Halt ': es)))) a -> Eff ff es a
- runParallelIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a
- parallelToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Parallel ~~> m
- runPollIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, UnliftIO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Poll ': es) a -> Eff ff es a
- runRaceIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, UnliftIO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Race ': es) a -> Eff ff es a
- runHaltIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Halt ': es) a -> Eff ff es a
- raceToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Race ~~> m
- pollToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Poll ~~> m
- haltToIO :: forall (m :: Type -> Type). MonadIO m => Halt ~~> m
- runParallelAsSequential :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a
- parallelToSequential :: forall (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]). Applicative (Eff ff es) => Parallel ~~> Eff ff es
- runForAsParallel :: forall (t :: Type -> Type) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Parallel :> es, Traversable t, Applicative (Eff ff es), Free c ff) => Eff ff (For t ': es) a -> Eff ff es a
Documentation
data Parallel (a :: Type -> Type) b where Source #
An Applicative
-based effect for executing computations in parallel.
Constructors
LiftP2 | Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function. |
Instances
PolyHFunctor Parallel Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
HFunctor Parallel Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type FormOf Parallel Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type LabelOf Parallel Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf Parallel Source # | |
Defined in Data.Effect.Concurrent.Parallel |
data Halt (a :: Type -> Type) b where Source #
An effect that blocks a computation indefinitely.
Instances
FirstOrder Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
PolyHFunctor Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
HFunctor Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type FormOf Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type LabelOf Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel |
data Race (a :: Type -> Type) b where Source #
An effect that adopts the result of the computation that finishes first among two computations and cancels the other.
Constructors
Race :: forall (a :: Type -> Type) b. a b -> a b -> Race a b | Adopts the result of the computation that finishes first among two computations and cancels the other. |
Instances
PolyHFunctor Race Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
HFunctor Race Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type FormOf Race Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type LabelOf Race Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf Race Source # | |
Defined in Data.Effect.Concurrent.Parallel |
halt :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Halt :> es) => f a Source #
Blocks a computation indefinitely.
halt' :: forall {k} (key :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Halt es) => f a Source #
Blocks a computation indefinitely.
halt'' :: forall {k} (tag :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Halt :> es) => f a Source #
Blocks a computation indefinitely.
halt'_ :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Halt es) => f a Source #
Blocks a computation indefinitely.
data ParallelLabel Source #
Arguments
:: forall a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Parallel :> es) | |
=> (a -> b -> c1) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c1 |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall {k} (key :: k) a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Has key Parallel es) | |
=> (a -> b -> c1) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c1 |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall {k} (tag :: k) a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, Tagged tag Parallel :> es) | |
=> (a -> b -> c1) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c1 |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall a b c1 f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c2 :: (Type -> Type) -> Constraint). (Free c2 ff, f ~ Eff ff es, In Parallel es) | |
=> (a -> b -> c1) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c1 |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
race :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Race :> es) => f a -> f a -> f a Source #
Adopts the result of the computation that finishes first among two computations and cancels the other.
race' :: forall {k} (key :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Race es) => f a -> f a -> f a Source #
Adopts the result of the computation that finishes first among two computations and cancels the other.
race'' :: forall {k} (tag :: k) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Race :> es) => f a -> f a -> f a Source #
Adopts the result of the computation that finishes first among two computations and cancels the other.
race'_ :: forall a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Race es) => f a -> f a -> f a Source #
Adopts the result of the computation that finishes first among two computations and cancels the other.
newtype Concurrently (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a Source #
A wrapper that allows using the Parallel
effect in the form of Applicative
/
Alternative
instances.
Constructors
Concurrently | |
Fields
|
Instances
Arguments
:: forall a b c d (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (con :: (Type -> Type) -> Constraint). (Parallel :> es, Free con ff) | |
=> (a -> b -> c -> d) | A function that aggregates the three execution results. |
-> Eff ff es a | The first action to be executed in parallel. |
-> Eff ff es b | The second action to be executed in parallel. |
-> Eff ff es c | The third action to be executed in parallel. |
-> Eff ff es d |
Executes three actions in parallel and blocks until all are complete. Finally, aggregates the execution results based on the specified function.
data Poll (a :: Type -> Type) b where Source #
An effect that realizes polling and cancellation of actions running in parallel.
Constructors
Poldl | Performs polling on an action running in parallel in the form of a fold. First, the parallel execution of two actions begins. When the execution of the first action completes, polling on the second
action is performed at that point, and the result is passed to the
folding function. If the function returns |
Instances
HFunctor Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type FormOf Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type LabelOf Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel |
Arguments
:: forall a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Poll :> es) | |
=> (a -> Maybe b -> f (Either r a)) | |
-> f a | |
-> f b | The second action to be executed in parallel; the target of polling. |
-> f r |
Performs polling on an action running in parallel in the form of a fold.
First, the parallel execution of two actions begins.
When the execution of the first action completes, polling on the second
action is performed at that point, and the result is passed to the
folding function. If the function returns Left
, the folding terminates
and it becomes the final result. If the second action is not yet
complete, it is canceled. If the function returns Right
, the folding
continues, and the same process repeats.
Arguments
:: forall {k} (key :: k) a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Poll es) | |
=> (a -> Maybe b -> f (Either r a)) | |
-> f a | |
-> f b | The second action to be executed in parallel; the target of polling. |
-> f r |
Performs polling on an action running in parallel in the form of a fold.
First, the parallel execution of two actions begins.
When the execution of the first action completes, polling on the second
action is performed at that point, and the result is passed to the
folding function. If the function returns Left
, the folding terminates
and it becomes the final result. If the second action is not yet
complete, it is canceled. If the function returns Right
, the folding
continues, and the same process repeats.
Arguments
:: forall {k} (tag :: k) a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Poll :> es) | |
=> (a -> Maybe b -> f (Either r a)) | |
-> f a | |
-> f b | The second action to be executed in parallel; the target of polling. |
-> f r |
Performs polling on an action running in parallel in the form of a fold.
First, the parallel execution of two actions begins.
When the execution of the first action completes, polling on the second
action is performed at that point, and the result is passed to the
folding function. If the function returns Left
, the folding terminates
and it becomes the final result. If the second action is not yet
complete, it is canceled. If the function returns Right
, the folding
continues, and the same process repeats.
Arguments
:: forall a b r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Poll es) | |
=> (a -> Maybe b -> f (Either r a)) | |
-> f a | |
-> f b | The second action to be executed in parallel; the target of polling. |
-> f r |
Performs polling on an action running in parallel in the form of a fold.
First, the parallel execution of two actions begins.
When the execution of the first action completes, polling on the second
action is performed at that point, and the result is passed to the
folding function. If the function returns Left
, the folding terminates
and it becomes the final result. If the second action is not yet
complete, it is canceled. If the function returns Right
, the folding
continues, and the same process repeats.
Arguments
:: forall a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Poll :> es, Applicative (Eff ff es), Free c ff) | |
=> Eff ff es a | The action that controls the cancellation. |
-> Eff ff es b | The action to be canceled. |
-> Eff ff es (a, Maybe b) |
Executes two actions in parallel. If the first action completes before the second, the second action is canceled.
Arguments
:: forall a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Poll :> es, Applicative (Eff ff es), Free c ff) | |
=> Eff ff es a | The action to be canceled. |
-> Eff ff es b | The action that controls the cancellation. |
-> Eff ff es (Maybe a, b) |
Executes two actions in parallel. If the second action completes before the first, the first action is canceled.
data For (t :: Type -> Type) (a :: Type -> Type) b where Source #
An effect for parallel computations based on a Traversable
container t
.
Constructors
For :: forall (t :: Type -> Type) (a :: Type -> Type) a1. t (a a1) -> For t a (t a1) | Executes in parallel the actions stored within a |
Instances
PolyHFunctor (For t) Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
Functor t => HFunctor (For t) Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type FormOf (For t) Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type LabelOf (For t) Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf (For t) Source # | |
Defined in Data.Effect.Concurrent.Parallel |
for :: forall t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, For t :> es) => t (f a) -> f (t a) Source #
Executes in parallel the actions stored within a Traversable
container t
.
for' :: forall {k} (key :: k) t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (For t) es) => t (f a) -> f (t a) Source #
Executes in parallel the actions stored within a Traversable
container t
.
for'' :: forall {k} (tag :: k) t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (For t) :> es) => t (f a) -> f (t a) Source #
Executes in parallel the actions stored within a Traversable
container t
.
for'_ :: forall t a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (For t) es) => t (f a) -> f (t a) Source #
Executes in parallel the actions stored within a Traversable
container t
.
forToParallel :: forall (t :: Type -> Type) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Parallel :> es, Traversable t, Applicative (Eff ff es), Free c ff) => For t (Eff ff es) a -> Eff ff es a Source #
Converts the Traversable
container-based parallel computation effect For
into the Applicative
-based parallel computation effect Parallel
.
runConcurrentIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, forall (es' :: [Effect]). Monad (Eff ff es'), Free c ff) => Eff ff (Parallel ': (Race ': (Poll ': (Halt ': es)))) a -> Eff ff es a Source #
runParallelIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a Source #
parallelToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Parallel ~~> m Source #
runPollIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, UnliftIO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Poll ': es) a -> Eff ff es a Source #
runRaceIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, UnliftIO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Race ': es) a -> Eff ff es a Source #
runHaltIO :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Halt ': es) a -> Eff ff es a Source #
runParallelAsSequential :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a Source #