data-effects-0.4.0.2: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2024-2025 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Effect.Concurrent.Parallel

Description

Effects for parallel computations.

Synopsis

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

  • :: (a -> b -> c)

    A function that aggregates the two execution results.

  • -> f a

    The first action to be executed in parallel.

  • -> f b

    The second action to be executed in parallel.

  • -> Parallel f c
     

Instances

Instances details
HFunctor Parallel Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

hfmap :: (forall x. f x -> g x) -> Parallel f a -> Parallel g a #

type LabelOf Parallel Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type OrderOf Parallel Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

data Halt :: Effect where Source #

An effect that blocks a computation indefinitely.

Constructors

Halt :: Halt f a

Blocks a computation indefinitely.

Instances

Instances details
FirstOrder Halt Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

HFunctor Halt Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

hfmap :: (forall x. f x -> g x) -> Halt f a -> Halt g a #

type LabelOf Halt Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type OrderOf Halt Source # 
Instance details

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

Instances details
HFunctor Race Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

hfmap :: (forall x. f x -> g x) -> Race f a -> Race g a #

type LabelOf Race Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type OrderOf Race Source # 
Instance details

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.

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.

liftP2'_ Source #

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.

liftP2'' Source #

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.

liftP2' Source #

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.

liftP2 Source #

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

Instances details
(Race :> es, Halt :> es, Parallel :> es, Applicative (Eff ff es), Free c ff) => Alternative (Concurrently ff es) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

empty :: Concurrently ff es a #

(<|>) :: Concurrently ff es a -> Concurrently ff es a -> Concurrently ff es a #

some :: Concurrently ff es a -> Concurrently ff es [a] #

many :: Concurrently ff es a -> Concurrently ff es [a] #

(Parallel :> es, Applicative (Eff ff es), Free c ff) => Applicative (Concurrently ff es) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

pure :: a -> Concurrently ff es a #

(<*>) :: Concurrently ff es (a -> b) -> Concurrently ff es a -> Concurrently ff es b #

liftA2 :: (a -> b -> c) -> Concurrently ff es a -> Concurrently ff es b -> Concurrently ff es c #

(*>) :: Concurrently ff es a -> Concurrently ff es b -> Concurrently ff es b #

(<*) :: Concurrently ff es a -> Concurrently ff es b -> Concurrently ff es a #

Functor (Eff ff es) => Functor (Concurrently ff es) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

fmap :: (a -> b) -> Concurrently ff es a -> Concurrently ff es b #

(<$) :: a -> Concurrently ff es b -> Concurrently ff es a #

liftP3 Source #

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 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.

Fields

  • :: (a -> Maybe b -> f (Either r a))

    A function for folding.

  • -> f a

    The first action to be executed in parallel.

  • -> f b

    The second action to be executed in parallel; the target of polling.

  • -> Poll f r
     

Instances

Instances details
HFunctor Poll Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

hfmap :: (forall x. f x -> g x) -> Poll f a -> Poll g a #

type LabelOf Poll Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type OrderOf Poll Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

poldl'_ Source #

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.

poldl'' Source #

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.

poldl' Source #

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.

poldl Source #

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.

cancels Source #

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.

cancelBy Source #

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 Traversable container t.

Instances

Instances details
Functor t => HFunctor (For t) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

Methods

hfmap :: (forall x. f x -> g x) -> For t f a -> For t g a #

type LabelOf (For t) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type LabelOf (For t) = ForLabel
type OrderOf (For t) Source # 
Instance details

Defined in Data.Effect.Concurrent.Parallel

type OrderOf (For t) = 'HigherOrder

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 #

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 #

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 #