effectful-2.2.1.0: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Concurrent.Async

Description

Synopsis

Effect

data Concurrent :: Effect Source #

Provide the ability to run Eff computations concurrently in multiple threads and communicate between them.

Warning: unless you stick to high level functions from the withAsync family, the Concurrent effect makes it possible to escape the scope of any scoped effect operation. Consider the following:

>>> import qualified Effectful.Reader.Static as R
>>> printAsk msg = liftIO . putStrLn . (msg ++) . (": " ++) =<< R.ask
>>> :{
  runEff . R.runReader "GLOBAL" . runConcurrent $ do
    a <- R.local (const "LOCAL") $ do
      a <- async $ do
        printAsk "child (first)"
        threadDelay 20000
        printAsk "child (second)"
      threadDelay 10000
      printAsk "parent (inside)"
      pure a
    printAsk "parent (outside)"
    wait a
:}
child (first): LOCAL
parent (inside): LOCAL
parent (outside): GLOBAL
child (second): LOCAL

Note that the asynchronous computation doesn't respect the scope of local, i.e. the child thread still behaves like it's inside the local block, even though the parent thread already got out of it.

This is because the value provided by the Reader effect is thread local, i.e. each thread manages its own version of it. For the Reader it is the only reasonable behavior, it wouldn't be very useful if its "read only" value was affected by calls to local from its parent or child threads.

However, the cut isn't so clear if it comes to effects that provide access to a mutable state. That's why statically dispatched State and Writer effects come in two flavors, local and shared:

>>> import qualified Effectful.State.Static.Local as SL
>>> :{
  runEff . SL.execState "Hi" . runConcurrent $ do
    replicateConcurrently_ 3 $ SL.modify (++ "!")
:}
"Hi"
>>> import qualified Effectful.State.Static.Shared as SS
>>> :{
  runEff . SS.execState "Hi" . runConcurrent $ do
    replicateConcurrently_ 3 $ SS.modify (++ "!")
:}
"Hi!!!"

In the first example state updates made concurrently are not reflected in the parent thread because the value is thread local, but in the second example they are, because the value is shared.

Instances

Instances details
type DispatchOf Concurrent Source # 
Instance details

Defined in Effectful.Concurrent.Effect

data StaticRep Concurrent Source # 
Instance details

Defined in Effectful.Concurrent.Effect

Handlers

runConcurrent :: IOE :> es => Eff (Concurrent ': es) a -> Eff es a Source #

Run the Concurrent effect.

Asynchronous actions

data Async a #

An asynchronous action spawned by async or withAsync. Asynchronous actions are executed in a separate thread, and operations are provided for waiting for asynchronous actions to complete and obtaining their results (see e.g. wait).

Instances

Instances details
Functor Async 
Instance details

Defined in Control.Concurrent.Async

Methods

fmap :: (a -> b) -> Async a -> Async b #

(<$) :: a -> Async b -> Async a #

Eq (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

(==) :: Async a -> Async a -> Bool #

(/=) :: Async a -> Async a -> Bool #

Ord (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

compare :: Async a -> Async a -> Ordering #

(<) :: Async a -> Async a -> Bool #

(<=) :: Async a -> Async a -> Bool #

(>) :: Async a -> Async a -> Bool #

(>=) :: Async a -> Async a -> Bool #

max :: Async a -> Async a -> Async a #

min :: Async a -> Async a -> Async a #

Hashable (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

hashWithSalt :: Int -> Async a -> Int #

hash :: Async a -> Int #

High-level API

Spawning with automatic cancelation

withAsync :: Concurrent :> es => Eff es a -> (Async a -> Eff es b) -> Eff es b Source #

Lifted withAsync.

withAsyncBound :: Concurrent :> es => Eff es a -> (Async a -> Eff es b) -> Eff es b Source #

withAsyncOn :: Concurrent :> es => Int -> Eff es a -> (Async a -> Eff es b) -> Eff es b Source #

Lifted withAsyncOn.

withAsyncWithUnmask :: Concurrent :> es => ((forall c. Eff es c -> Eff es c) -> Eff es a) -> (Async a -> Eff es b) -> Eff es b Source #

withAsyncOnWithUnmask :: Concurrent :> es => Int -> ((forall c. Eff es c -> Eff es c) -> Eff es a) -> (Async a -> Eff es b) -> Eff es b Source #

Querying Asyncs

wait :: Concurrent :> es => Async a -> Eff es a Source #

Lifted wait.

poll :: Concurrent :> es => Async a -> Eff es (Maybe (Either SomeException a)) Source #

Lifted poll.

asyncThreadId :: Async a -> ThreadId #

Returns the ThreadId of the thread running the given Async.

cancel :: Concurrent :> es => Async a -> Eff es () Source #

Lifted cancel.

cancelWith :: (Exception e, Concurrent :> es) => Async a -> e -> Eff es () Source #

Lifted cancelWith.

data AsyncCancelled #

The exception thrown by cancel to terminate a thread.

Constructors

AsyncCancelled 

compareAsyncs :: Async a -> Async b -> Ordering #

Compare two Asyncs that may have different types by their ThreadId.

High-level utilities

race :: Concurrent :> es => Eff es a -> Eff es b -> Eff es (Either a b) Source #

Lifted race.

race_ :: Concurrent :> es => Eff es a -> Eff es b -> Eff es () Source #

Lifted race_.

concurrently :: Concurrent :> es => Eff es a -> Eff es b -> Eff es (a, b) Source #

Lifted concurrently.

concurrently_ :: Concurrent :> es => Eff es a -> Eff es b -> Eff es () Source #

mapConcurrently :: (Traversable f, Concurrent :> es) => (a -> Eff es b) -> f a -> Eff es (f b) Source #

forConcurrently :: (Traversable f, Concurrent :> es) => f a -> (a -> Eff es b) -> Eff es (f b) Source #

mapConcurrently_ :: (Foldable f, Concurrent :> es) => (a -> Eff es b) -> f a -> Eff es () Source #

forConcurrently_ :: (Foldable f, Concurrent :> es) => f a -> (a -> Eff es b) -> Eff es () Source #

Concurrently

newtype Concurrently es a Source #

Lifted Concurrently.

Constructors

Concurrently 

Fields

Instances

Instances details
Concurrent :> es => Alternative (Concurrently es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

empty :: Concurrently es a #

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

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

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

Concurrent :> es => Applicative (Concurrently es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

pure :: a -> Concurrently es a #

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

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

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

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

Functor (Concurrently es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

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

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

(Concurrent :> es, Monoid a) => Monoid (Concurrently es a) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

mempty :: Concurrently es a #

mappend :: Concurrently es a -> Concurrently es a -> Concurrently es a #

mconcat :: [Concurrently es a] -> Concurrently es a #

(Concurrent :> es, Semigroup a) => Semigroup (Concurrently es a) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

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

sconcat :: NonEmpty (Concurrently es a) -> Concurrently es a #

stimes :: Integral b => b -> Concurrently es a -> Concurrently es a #

Conc

data Conc :: [Effect] -> Type -> Type Source #

Lifted Conc.

Instances

Instances details
Alternative (Conc es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

empty :: Conc es a #

(<|>) :: Conc es a -> Conc es a -> Conc es a #

some :: Conc es a -> Conc es [a] #

many :: Conc es a -> Conc es [a] #

Applicative (Conc es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

pure :: a -> Conc es a #

(<*>) :: Conc es (a -> b) -> Conc es a -> Conc es b #

liftA2 :: (a -> b -> c) -> Conc es a -> Conc es b -> Conc es c #

(*>) :: Conc es a -> Conc es b -> Conc es b #

(<*) :: Conc es a -> Conc es b -> Conc es a #

Functor (Conc es) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

fmap :: (a -> b) -> Conc es a -> Conc es b #

(<$) :: a -> Conc es b -> Conc es a #

Monoid a => Monoid (Conc es a) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

mempty :: Conc es a #

mappend :: Conc es a -> Conc es a -> Conc es a #

mconcat :: [Conc es a] -> Conc es a #

Semigroup a => Semigroup (Conc es a) Source # 
Instance details

Defined in Effectful.Concurrent.Async

Methods

(<>) :: Conc es a -> Conc es a -> Conc es a #

sconcat :: NonEmpty (Conc es a) -> Conc es a #

stimes :: Integral b => b -> Conc es a -> Conc es a #

conc :: Eff es a -> Conc es a Source #

Lifted conc.

runConc :: Concurrent :> es => Conc es a -> Eff es a Source #

Lifted runConc.

data ConcException #

Things that can go wrong in the structure of a Conc. These are programmer errors.

Since: unliftio-0.2.9.0

Instances

Instances details
Exception ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Generic ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Associated Types

type Rep ConcException :: Type -> Type #

Show ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Eq ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Ord ConcException 
Instance details

Defined in UnliftIO.Internals.Async

type Rep ConcException 
Instance details

Defined in UnliftIO.Internals.Async

type Rep ConcException = D1 ('MetaData "ConcException" "UnliftIO.Internals.Async" "unliftio-0.2.23.0-8Xz3hC2ra6eGMVihZEzUzT" 'False) (C1 ('MetaCons "EmptyWithNoAlternative" 'PrefixI 'False) (U1 :: Type -> Type))

Pooled concurrency

pooledMapConcurrentlyN :: (Concurrent :> es, Traversable t) => Int -> (a -> Eff es b) -> t a -> Eff es (t b) Source #

pooledMapConcurrently :: (Concurrent :> es, Traversable t) => (a -> Eff es b) -> t a -> Eff es (t b) Source #

pooledMapConcurrentlyN_ :: (Concurrent :> es, Foldable f) => Int -> (a -> Eff es b) -> f a -> Eff es () Source #

pooledMapConcurrently_ :: (Concurrent :> es, Foldable f) => (a -> Eff es b) -> f a -> Eff es () Source #

pooledForConcurrentlyN :: (Concurrent :> es, Traversable t) => Int -> t a -> (a -> Eff es b) -> Eff es (t b) Source #

pooledForConcurrently :: (Concurrent :> es, Traversable t) => t a -> (a -> Eff es b) -> Eff es (t b) Source #

pooledForConcurrentlyN_ :: (Concurrent :> es, Foldable f) => Int -> f a -> (a -> Eff es b) -> Eff es () Source #

pooledForConcurrently_ :: (Concurrent :> es, Foldable f) => f a -> (a -> Eff es b) -> Eff es () Source #

Specialised operations

STM operations

waitSTM :: Async a -> STM a #

A version of wait that can be used inside an STM transaction.

pollSTM :: Async a -> STM (Maybe (Either SomeException a)) #

A version of poll that can be used inside an STM transaction.

waitCatchSTM :: Async a -> STM (Either SomeException a) #

A version of waitCatch that can be used inside an STM transaction.

Waiting for multiple Asyncs

waitAny :: Concurrent :> es => [Async a] -> Eff es (Async a, a) Source #

Lifted waitAny.

waitAnyCancel :: Concurrent :> es => [Async a] -> Eff es (Async a, a) Source #

waitEither :: Concurrent :> es => Async a -> Async b -> Eff es (Either a b) Source #

Lifted waitEither.

waitEither_ :: Concurrent :> es => Async a -> Async b -> Eff es () Source #

Lifted waitEither_.

waitBoth :: Concurrent :> es => Async a -> Async b -> Eff es (a, b) Source #

Lifted waitBoth.

Waiting for multiple Asyncs in STM

waitAnySTM :: [Async a] -> STM (Async a, a) #

A version of waitAny that can be used inside an STM transaction.

Since: async-2.1.0

waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) #

A version of waitAnyCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM :: Async a -> Async b -> STM (Either a b) #

A version of waitEither that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) #

A version of waitEitherCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM_ :: Async a -> Async b -> STM () #

A version of waitEither_ that can be used inside an STM transaction.

Since: async-2.1.0

waitBothSTM :: Async a -> Async b -> STM (a, b) #

A version of waitBoth that can be used inside an STM transaction.

Since: async-2.1.0

Low-level API

Spawning (low-level API)

async :: Concurrent :> es => Eff es a -> Eff es (Async a) Source #

Lifted async.

asyncBound :: Concurrent :> es => Eff es a -> Eff es (Async a) Source #

Lifted asyncBound.

asyncOn :: Concurrent :> es => Int -> Eff es a -> Eff es (Async a) Source #

Lifted asyncOn.

asyncWithUnmask :: Concurrent :> es => ((forall b. Eff es b -> Eff es b) -> Eff es a) -> Eff es (Async a) Source #

asyncOnWithUnmask :: Concurrent :> es => Int -> ((forall b. Eff es b -> Eff es b) -> Eff es a) -> Eff es (Async a) Source #

Linking

link :: Concurrent :> es => Async a -> Eff es () Source #

Lifted link.

linkOnly :: Concurrent :> es => (SomeException -> Bool) -> Async a -> Eff es () Source #

Lifted linkOnly.

link2 :: Concurrent :> es => Async a -> Async b -> Eff es () Source #

Lifted link2.

link2Only :: Concurrent :> es => (SomeException -> Bool) -> Async a -> Async b -> Eff es () Source #

Lifted link2Only.