Control.Concurrent.MVar (original) (raw)
Description
An `[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")` t
is a mutable location that is either empty or contains a value of type t
. It has two fundamental operations: [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
which fills an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
if it is empty and blocks otherwise, and[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
which empties an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
if it is full and blocks otherwise. They can be used in multiple different ways:
- As synchronized mutable variables,
- As channels, with
[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
and[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
as receive and send, and - As a binary semaphore
`[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")` ()
, with[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
and[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
as wait and signal.
They were introduced in the paper"Concurrent Haskell" by Simon Peyton Jones, Andrew Gordon and Sigbjorn Finne, though some details of their implementation have since then changed (in particular, a put on a full [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
used to error, but now merely blocks.)
Applicability
[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s offer more flexibility than [IORef](Data-IORef.html#v:IORef "Data.IORef")
s, but less flexibility than [STM](GHC-Conc.html#v:STM "GHC.Conc")
. They are appropriate for building synchronization primitives and performing simple inter-thread communication; however they are very simple and susceptible to race conditions, deadlocks or uncaught exceptions. Do not use them if you need to perform larger atomic operations such as reading from multiple variables: use [STM](GHC-Conc.html#v:STM "GHC.Conc")
instead.
In particular, the "bigger" functions in this module ([swapMVar](Control-Concurrent-MVar.html#v:swapMVar "Control.Concurrent.MVar")
,[withMVar](Control-Concurrent-MVar.html#v:withMVar "Control.Concurrent.MVar")
, [modifyMVar_](Control-Concurrent-MVar.html#v:modifyMVar%5F "Control.Concurrent.MVar")
and [modifyMVar](Control-Concurrent-MVar.html#v:modifyMVar "Control.Concurrent.MVar")
) are simply the composition of a [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
followed by a [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
with exception safety. These have atomicity guarantees only if all other threads perform a [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
before a [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
as well; otherwise, they may block.
Fairness
No thread can be blocked indefinitely on an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
unless another thread holds that [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
indefinitely. One usual implementation of this fairness guarantee is that threads blocked on an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
are served in a first-in-first-out fashion (this is what GHC does), but this is not guaranteed in the semantics.
Gotchas
Like many other Haskell data structures, [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s are lazy. This means that if you place an expensive unevaluated thunk inside an[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
, it will be evaluated by the thread that consumes it, not the thread that produced it. Be sure to evaluate
values to be placed in an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
to the appropriate normal form, or utilize a strictMVar
provided by the strict-concurrency package.
Ordering
[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
operations are always observed to take place in the order they are written in the program, regardless of the memory model of the underlying machine. This is in contrast to [IORef](Data-IORef.html#v:IORef "Data.IORef")
operations which may appear out-of-order to another thread in some cases.
Example
Consider the following concurrent data structure, a skip channel. This is a channel for an intermittent source of high bandwidth information (for example, mouse movement events.) Writing to the channel never blocks, and reading from the channel only returns the most recent value, or blocks if there are no new values. Multiple readers are supported with a dupSkipChan
operation.
A skip channel is a pair of [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s. The first [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
contains the current value, and a list of semaphores that need to be notified when it changes. The second [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is a semaphore for this particular reader: it is full if there is a value in the channel that this reader has not read yet, and empty otherwise.
data SkipChan a = SkipChan (MVar (a, [MVar ()])) (MVar ())
newSkipChan :: IO (SkipChan a) newSkipChan = do sem <- newEmptyMVar main <- newMVar (undefined, [sem]) return (SkipChan main sem)
putSkipChan :: SkipChan a -> a -> IO () putSkipChan (SkipChan main ) v = do (, sems) <- takeMVar main putMVar main (v, []) mapM_ (\sem -> putMVar sem ()) sems
getSkipChan :: SkipChan a -> IO a getSkipChan (SkipChan main sem) = do takeMVar sem (v, sems) <- takeMVar main putMVar main (v, sem : sems) return v
dupSkipChan :: SkipChan a -> IO (SkipChan a) dupSkipChan (SkipChan main _) = do sem <- newEmptyMVar (v, sems) <- takeMVar main putMVar main (v, sem : sems) return (SkipChan main sem)
This example was adapted from the original Concurrent Haskell paper. For more examples of [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s being used to build higher-level synchronization primitives, see [Chan](Control-Concurrent.html#v:Chan "Control.Concurrent")
and[QSem](Control-Concurrent.html#v:QSem "Control.Concurrent")
.
Synopsis
- data MVar a
- newEmptyMVar :: IO (MVar a)
- newMVar :: a -> IO (MVar a)
- takeMVar :: MVar a -> IO a
- putMVar :: MVar a -> a -> IO ()
- readMVar :: MVar a -> IO a
- swapMVar :: MVar a -> a -> IO a
- tryTakeMVar :: MVar a -> IO (Maybe a)
- tryPutMVar :: MVar a -> a -> IO Bool
- isEmptyMVar :: MVar a -> IO Bool
- withMVar :: MVar a -> (a -> IO b) -> IO b
- withMVarMasked :: MVar a -> (a -> IO b) -> IO b
- modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
- modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
- modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO ()
- modifyMVarMasked :: MVar a -> (a -> IO (a, b)) -> IO b
- tryReadMVar :: MVar a -> IO (Maybe a)
- mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a))
- addMVarFinalizer :: MVar a -> IO () -> IO ()
An [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.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
takeMVar :: MVar a -> IO a Source #
Return the contents of the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. If the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is currently empty, [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
will wait until it is full. After a [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
, the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is left empty.
There are two further important properties of [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
:
[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
is single-wakeup. That is, if there are multiple threads blocked in[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
, and the[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
becomes full, only one thread will be woken up. The runtime guarantees that the woken thread completes its[takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
operation.- When multiple threads are blocked on an
[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
, they are woken up in FIFO order. This is useful for providing fairness properties of abstractions built using[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s.
putMVar :: MVar a -> a -> IO () Source #
Put a value into an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. If the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is currently full,[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
will wait until it becomes empty.
There are two further important properties of [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
:
[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
is single-wakeup. That is, if there are multiple threads blocked in[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
, and the[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
becomes empty, only one thread will be woken up. The runtime guarantees that the woken thread completes its[putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
operation.- When multiple threads are blocked on an
[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
, they are woken up in FIFO order. This is useful for providing fairness properties of abstractions built using[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
s.
readMVar :: MVar a -> IO a Source #
Atomically read the contents of an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. If the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is currently empty, [readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
will wait until it is full.[readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
is guaranteed to receive the next [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
.
[readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
is multiple-wakeup, so when multiple readers are blocked on an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
, all of them are woken up at the same time. The runtime guarantees that all woken threads complete their [readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
operation.
Compatibility note: Prior to base 4.7, [readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
was a combination of [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
and [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
. This mean that in the presence of other threads attempting to [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
, [readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
could block. Furthermore, [readMVar](Control-Concurrent-MVar.html#v:readMVar "Control.Concurrent.MVar")
would not receive the next [putMVar](Control-Concurrent-MVar.html#v:putMVar "Control.Concurrent.MVar")
if there was already a pending thread blocked on [takeMVar](Control-Concurrent-MVar.html#v:takeMVar "Control.Concurrent.MVar")
. The old behavior can be recovered by implementing 'readMVar as follows:
readMVar :: MVar a -> IO a readMVar m = mask_ $ do a <- takeMVar m putMVar m a return a
swapMVar :: MVar a -> a -> IO a Source #
Take a value from an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
, put a new value into the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
and return the value taken. This function is atomic only if there are no other producers for this [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. In other words, it cannot guarantee that, by the time [swapMVar](Control-Concurrent-MVar.html#v:swapMVar "Control.Concurrent.MVar")
gets the chance to write to the MVar, the value of the MVar has not been altered by a write operation from another thread.
isEmptyMVar :: MVar a -> IO Bool Source #
Check whether a given [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
is empty.
Notice that the boolean value returned is just a snapshot of the state of the MVar. By the time you get to react on its result, the MVar may have been filled (or emptied) - so be extremely careful when using this operation. Use [tryTakeMVar](Control-Concurrent-MVar.html#v:tryTakeMVar "Control.Concurrent.MVar")
instead if possible.
withMVar :: MVar a -> (a -> IO b) -> IO b Source #
[withMVar](Control-Concurrent-MVar.html#v:withMVar "Control.Concurrent.MVar")
is an exception-safe wrapper for operating on the contents of an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. This operation is exception-safe: it will replace the original contents of the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
if an exception is raised (seeControl.Exception). However, it is only atomic if there are no other producers for this [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. In other words, it cannot guarantee that, by the time [withMVar](Control-Concurrent-MVar.html#v:withMVar "Control.Concurrent.MVar")
gets the chance to write to the MVar, the value of the MVar has not been altered by a write operation from another thread.
modifyMVar_ :: MVar a -> (a -> IO a) -> IO () Source #
An exception-safe wrapper for modifying the contents of an [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. Like [withMVar](Control-Concurrent-MVar.html#v:withMVar "Control.Concurrent.MVar")
, [modifyMVar](Control-Concurrent-MVar.html#v:modifyMVar "Control.Concurrent.MVar")
will replace the original contents of the [MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
if an exception is raised during the operation. This function is only atomic if there are no other producers for this[MVar](Control-Concurrent-MVar.html#t:MVar "Control.Concurrent.MVar")
. In other words, it cannot guarantee that, by the time[modifyMVar_](Control-Concurrent-MVar.html#v:modifyMVar%5F "Control.Concurrent.MVar")
gets the chance to write to the MVar, the value of the MVar has not been altered by a write operation from another thread.