Copyright | (c) 2024-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Data.Effect.Concurrent.Parallel
Description
Effects for parallel computations.
Synopsis
- data Parallel :: Effect where
- data Halt :: Effect where
- data Race :: Effect where
- data HaltLabel
- halt'_ :: forall (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Halt es) => f a
- halt'' :: forall tag (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag Halt) es) => f a
- halt' :: forall key (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key Halt es) => f a
- halt :: forall (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Halt es) => f a
- data ParallelLabel
- data RaceLabel
- race'_ :: forall (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Race es) => f a -> f a -> f a
- race'' :: forall tag (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag Race) es) => f a -> f a -> f a
- race' :: forall key (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key Race es) => f a -> f a -> f a
- race :: forall (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Race es) => f a -> f a -> f a
- liftP2'_ :: forall (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Parallel es) => (a -> b -> c) -> f a -> f b -> f c
- liftP2'' :: forall tag (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag Parallel) es) => (a -> b -> c) -> f a -> f b -> f c
- liftP2' :: forall key (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key Parallel es) => (a -> b -> c) -> f a -> f b -> f c
- liftP2 :: forall (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Parallel es) => (a -> b -> c) -> f a -> f b -> f c
- newtype Concurrently ff es a = Concurrently {
- runConcurrently :: Eff ff es a
- liftP3 :: forall a b c d es ff con. (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 :: Effect where
- data PollLabel
- poldl'_ :: forall (a :: Type) (b :: Type) (r :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Poll es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- poldl'' :: forall tag (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 key (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 (a :: Type) (b :: Type) (r :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Poll es) => (a -> Maybe b -> f (Either r a)) -> f a -> f b -> f r
- cancels :: forall a b es ff c. (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 ff c. (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) :: Effect where
- data ForLabel
- for'_ :: forall (t :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (For t) es) => t (f a) -> f (t a)
- for'' :: forall tag (t :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (For t)) es) => t (f a) -> f (t a)
- for' :: forall key (t :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (For t) es) => t (f a) -> f (t a)
- for :: forall (t :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (For t) es) => t (f a) -> f (t a)
- forToParallel :: forall t a es ff c. (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 ff c. (UnliftIO :> es, Emb IO :> es, forall es'. Monad (Eff ff es'), Free c ff) => Eff ff (Parallel ': (Race ': (Poll ': (Halt ': es)))) a -> Eff ff es a
- runParallelIO :: forall a es ff c. (UnliftIO :> es, Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a
- parallelToIO :: MonadUnliftIO m => Parallel ~~> m
- runPollIO :: forall a es ff c. (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 ff c. (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 ff c. (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Halt ': es) a -> Eff ff es a
- raceToIO :: MonadUnliftIO m => Race ~~> m
- pollToIO :: MonadUnliftIO m => Poll ~~> m
- haltToIO :: MonadIO m => Halt ~~> m
- runParallelAsSequential :: forall a es ff c. (Applicative (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a
- parallelToSequential :: Applicative (Eff ff es) => Parallel ~~> Eff ff es
- runForAsParallel :: forall t a es ff c. (Parallel :> es, Traversable t, Applicative (Eff ff es), Free c ff) => Eff ff (For t ': es) a -> Eff ff es a
Documentation
data Parallel :: Effect 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. |
Fields
|
Instances
HFunctor 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 :: Effect where Source #
An effect that blocks a computation indefinitely.
Instances
FirstOrder Halt Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
HFunctor 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 :: Effect where Source #
An effect that adopts the result of the computation that finishes first among two computations and cancels the other.
Constructors
Race :: f a -> f a -> Race f a | Adopts the result of the computation that finishes first among two computations and cancels the other. |
Instances
HFunctor 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 :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Halt es) => f a Source #
Blocks a computation indefinitely.
halt'' :: forall tag (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag Halt) es) => f a Source #
Blocks a computation indefinitely.
halt' :: forall key (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key Halt es) => f a Source #
Blocks a computation indefinitely.
halt :: forall (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Halt es) => f a Source #
Blocks a computation indefinitely.
data ParallelLabel Source #
race'_ :: forall (a :: Type) f es ff c. (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.
race'' :: forall tag (a :: Type) f es ff c. (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 key (a :: Type) f es ff c. (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 (a :: Type) f es ff c. (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.
Arguments
:: forall (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In Parallel es) | |
=> (a -> b -> c) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall tag (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag Parallel) es) | |
=> (a -> b -> c) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall key (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key Parallel es) | |
=> (a -> b -> c) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
Arguments
:: forall (a :: Type) (b :: Type) (c :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) Parallel es) | |
=> (a -> b -> c) | |
-> f a | |
-> f b | The second action to be executed in parallel. |
-> f c |
Executes two actions in parallel and blocks until both are complete. Finally, aggregates the execution results based on the specified function.
newtype Concurrently ff es 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 ff con. (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 :: Effect 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 LabelOf Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel | |
type OrderOf Poll Source # | |
Defined in Data.Effect.Concurrent.Parallel |
Arguments
:: forall (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 tag (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 key (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 (a :: Type) (b :: Type) (r :: Type) f es ff c. (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 a b es ff c. (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 ff c. (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) :: Effect where Source #
An effect for parallel computations based on a Traversable
container t
.
Constructors
For :: t (f a) -> For t f (t a) | Executes in parallel the actions stored within a |
for'_ :: forall (t :: Type -> Type) (a :: Type) f es ff c. (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
.
for'' :: forall tag (t :: Type -> Type) (a :: Type) f es ff c. (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 key (t :: Type -> Type) (a :: Type) f es ff c. (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 (t :: Type -> Type) (a :: Type) f es ff c. (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
.
forToParallel :: forall t a es ff c. (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 ff c. (UnliftIO :> es, Emb IO :> es, forall es'. Monad (Eff ff es'), Free c ff) => Eff ff (Parallel ': (Race ': (Poll ': (Halt ': es)))) a -> Eff ff es a Source #
runParallelIO :: forall a es ff c. (UnliftIO :> es, Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a Source #
parallelToIO :: MonadUnliftIO m => Parallel ~~> m Source #
runPollIO :: forall a es ff c. (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 ff c. (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 ff c. (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Halt ': es) a -> Eff ff es a Source #
runParallelAsSequential :: forall a es ff c. (Applicative (Eff ff es), Free c ff) => Eff ff (Parallel ': es) a -> Eff ff es a Source #
parallelToSequential :: Applicative (Eff ff es) => Parallel ~~> Eff ff es Source #
runForAsParallel :: forall t a es ff c. (Parallel :> es, Traversable t, Applicative (Eff ff es), Free c ff) => Eff ff (For t ': es) a -> Eff ff es a Source #