concurrency-1.11.0.0: Typeclasses, functions, and data types for concurrency and STM.

Copyright(c) 2018 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Classy.IORef

Contents

Description

Mutable references in a concurrency monad.

Deviations: There is no Eq instance for MonadConc the IORef type. Furthermore, the mkWeakIORef function is not provided.

Synopsis

IORefs

newIORef :: MonadConc m => a -> m (IORef m a) Source #

Create a new reference.

newIORef = newIORefN ""

Since: 1.6.0.0

readIORef :: MonadConc m => IORef m a -> m a Source #

Read the current value stored in a reference.

readIORef ioref = readForCAS ioref >>= peekTicket

Since: 1.6.0.0

writeIORef :: MonadConc m => IORef m a -> a -> m () Source #

Write a new value into an IORef, without imposing a memory barrier. This means that relaxed memory effects can be observed.

Since: 1.6.0.0

modifyIORef :: MonadConc m => IORef m a -> (a -> a) -> m () Source #

Mutate the contents of a IORef.

Be warned that modifyIORef does not apply the function strictly. This means if the program calls modifyIORef many times, but seldomly uses the value, thunks will pile up in memory resulting in a space leak. This is a common mistake made when using a IORef as a counter. For example, the following will likely produce a stack overflow:

ref <- newIORef 0
replicateM_ 1000000 $ modifyIORef ref (+1)
readIORef ref >>= print

To avoid this problem, use modifyIORef' instead.

Since: 1.6.0.0

modifyIORef' :: MonadConc m => IORef m a -> (a -> a) -> m () Source #

Strict version of modifyIORef

Since: 1.6.0.0

atomicModifyIORef :: MonadConc m => IORef m a -> (a -> (a, b)) -> m b Source #

Atomically modify the value stored in a reference. This imposes a full memory barrier.

Since: 1.6.0.0

atomicModifyIORef' :: MonadConc m => IORef m a -> (a -> (a, b)) -> m b Source #

Strict version of atomicModifyIORef. This forces both the value stored in the IORef as well as the value returned.

Since: 1.6.0.0

atomicWriteIORef :: MonadConc m => IORef m a -> a -> m () Source #

Replace the value stored in a reference, with the barrier-to-reordering property that atomicModifyIORef has.

atomicWriteIORef r a = atomicModifyIORef r $ const (a, ())

Since: 1.6.0.0

Memory Model

In a concurrent program, IORef operations may appear out-of-order to another thread, depending on the memory model of the underlying processor architecture. For example, on x86 (which uses total store order), loads can move ahead of stores. Consider this example:

iorefs :: MonadConc m => m (Bool, Bool)
iorefs = do
  r1 <- newIORef False
  r2 <- newIORef False

  x <- spawn $ writeIORef r1 True >> readIORef r2
  y <- spawn $ writeIORef r2 True >> readIORef r1

  (,) <$> readMVar x <*> readMVar y

Under a sequentially consistent memory model the possible results are (True, True), (True, False), and (False, True). Under total or partial store order, (False, False) is also a possible result, even though there is no interleaving of the threads which can lead to this.

We can see this by testing with different memory models:

> autocheckWay defaultWay SequentialConsistency relaxed
[pass] Never Deadlocks
[pass] No Exceptions
[fail] Consistent Result
       (False,True) S0---------S1----S0--S2----S0--

       (True,True) S0---------S1-P2----S1---S0---

       (True,False) S0---------S2----S1----S0---
False
> autocheckWay defaultWay TotalStoreOrder  relaxed
[pass] Never Deadlocks
[pass] No Exceptions
[fail] Consistent Result
        (False,True) S0---------S1----S0--S2----S0--

        (False,False) S0---------S1--P2----S1--S0---

        (True,False) S0---------S2----S1----S0---

        (True,True) S0---------S1-C-S2----S1---S0---
False

Traces for non-sequentially-consistent memory models show where writes to IORefs are committed, which makes a write visible to all threads rather than just the one which performed the write. Only writeIORef is broken up into separate write and commit steps, atomicModifyIORef is still atomic and imposes a memory barrier.