effectful-2.0.0.0: An easy to use, performant extensible effects library.
Safe HaskellNone
LanguageHaskell2010

Effectful.Concurrent.MVar.Strict

Description

Lifted Control.Concurrent.MVar with operations that force values put inside an MVar to WHNF.

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
data StaticRep Concurrent Source # 
Instance details

Defined in Effectful.Concurrent.Effect

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

MVar

data MVar a #

An MVar (pronounced "em-var") is a synchronising variable, used for communication between concurrent threads. It can be thought of as a box, which may be empty or full.

Instances

Instances details
Eq (MVar a)

Since: base-4.1.0.0

Instance details

Defined in GHC.MVar

Methods

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

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

newMVar :: Concurrent :> es => a -> Eff es (MVar a) Source #

Lifted newMVar that evaluates the value to WHNF.

takeMVar :: Concurrent :> es => MVar a -> Eff es a Source #

Lifted takeMVar.

putMVar :: Concurrent :> es => MVar a -> a -> Eff es () Source #

Lifted putMVar.

readMVar :: Concurrent :> es => MVar a -> Eff es a Source #

Lifted readMVar.

swapMVar :: Concurrent :> es => MVar a -> a -> Eff es a Source #

Lifted swapMVar that evaluates the new value to WHNF.

tryTakeMVar :: Concurrent :> es => MVar a -> Eff es (Maybe a) Source #

Lifted tryTakeMVar.

tryPutMVar :: Concurrent :> es => MVar a -> a -> Eff es Bool Source #

Lifted tryPutMVar that evaluates the new value to WHNF.

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

Lifted withMVar.

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

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

Lifted modifyMVar that evaluates the new value to WHNF.

modifyMVar_ :: Concurrent :> es => MVar a -> (a -> Eff es a) -> Eff es () Source #

Lifted modifyMVar_ that evaluates the new value to WHNF.

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

Lifted modifyMVarMasked that evaluates the new value to WHNF.

modifyMVarMasked_ :: Concurrent :> es => MVar a -> (a -> Eff es a) -> Eff es () Source #

Lifted modifyMVarMasked_ that evaluates the new value to WHNF.

tryReadMVar :: Concurrent :> es => MVar a -> Eff es (Maybe a) Source #

Lifted tryReadMVar.

mkWeakMVar :: Concurrent :> es => MVar a -> Eff es () -> Eff es (Weak (MVar a)) Source #

Lifted mkWeakMVar.