Merge branch 'ghc-generics' of http://darcs.haskell.org/packages/base into ghc-generics
[ghc-base.git] / Control / Concurrent / MVar.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Control.Concurrent.MVar
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  non-portable (concurrency)
12 --
13 -- An @'MVar' t@ is mutable location that is either empty or contains a
14 -- value of type @t@.  It has two fundamental operations: 'putMVar'
15 -- which fills an 'MVar' if it is empty and blocks otherwise, and
16 -- 'takeMVar' which empties an 'MVar' if it is full and blocks
17 -- otherwise.  They can be used in multiple different ways:
18 --
19 --  1. As synchronized mutable variables,
20 --  2. As channels, with 'takeMVar' and 'putMVar' as receive and send, and
21 --  3. As a binary semaphore @'MVar' ()@, with 'takeMVar' and 'putMVar' as
22 --     wait and signal.
23 --
24 -- They were introduced in the paper "Concurrent Haskell" by Simon
25 -- Peyton Jones, Andrew Gordon and Sigbjorn Finne, though some details
26 -- of their implementation have since then changed (in particular, a
27 -- put on a full MVar used to error, but now merely blocks.)
28 --
29 -- * Applicability
30 --
31 -- 'MVar's offer more flexibility than 'IORef's, but less flexibility
32 -- than 'STM'.  They are appropriate for building synchronization
33 -- primitives and performing simple interthread communication; however
34 -- they are very simple and susceptible to race conditions, deadlocks or
35 -- uncaught exceptions.  Do not use them if you need perform larger
36 -- atomic operations such as reading from multiple variables: use 'STM'
37 -- instead.
38 --
39 -- In particular, the "bigger" functions in this module ('readMVar',
40 -- 'swapMVar', 'withMVar', 'modifyMVar_' and 'modifyMVar') are simply
41 -- the composition of a 'takeMVar' followed by a 'putMVar' with
42 -- exception safety.
43 -- These only have atomicity guarantees if all other threads
44 -- perform a 'takeMVar' before a 'putMVar' as well;  otherwise, they may
45 -- block.
46 --
47 -- * Fairness
48 --
49 -- No thread can be blocked indefinitely on an 'MVar' unless another
50 -- thread holds that 'MVar' indefinitely.  One usual implementation of
51 -- this fairness guarantee is that threads blocked on an 'MVar' are
52 -- served in a first-in-first-out fashion, but this is not guaranteed
53 -- in the semantics.
54 --
55 -- * Gotchas
56 --
57 -- Like many other Haskell data structures, 'MVar's are lazy.  This
58 -- means that if you place an expensive unevaluated thunk inside an
59 -- 'MVar', it will be evaluated by the thread that consumes it, not the
60 -- thread that produced it.  Be sure to 'evaluate' values to be placed
61 -- in an 'MVar' to the appropriate normal form, or utilize a strict
62 -- MVar provided by the strict-concurrency package.
63 --
64 -- * Example
65 --
66 -- Consider the following concurrent data structure, a skip channel.
67 -- This is a channel for an intermittent source of high bandwidth
68 -- information (for example, mouse movement events.)  Writing to the
69 -- channel never blocks, and reading from the channel only returns the
70 -- most recent value, or blocks if there are no new values.  Multiple
71 -- readers are supported with a @dupSkipChan@ operation.
72 --
73 -- A skip channel is a pair of 'MVar's. The first 'MVar' contains the
74 -- current value, and a list of semaphores that need to be notified
75 -- when it changes. The second 'MVar' is a semaphore for this particular
76 -- reader: it is full if there is a value in the channel that this
77 -- reader has not read yet, and empty otherwise.
78 --
79 -- @
80 --     data SkipChan a = SkipChan (MVar (a, [MVar ()])) (MVar ())
81 --
82 --     newSkipChan :: IO (SkipChan a)
83 --     newSkipChan = do
84 --         sem <- newEmptyMVar
85 --         main <- newMVar (undefined, [sem])
86 --         return (SkipChan main sem)
87 --
88 --     putSkipChan :: SkipChan a -> a -> IO ()
89 --     putSkipChan (SkipChan main _) v = do
90 --         (_, sems) <- takeMVar main
91 --         putMVar main (v, [])
92 --         mapM_ (\sem -> putMVar sem ()) sems
93 --
94 --     getSkipChan :: SkipChan a -> IO a
95 --     getSkipChan (SkipChan main sem) = do
96 --         takeMVar sem
97 --         (v, sems) <- takeMVar main
98 --         putMVar main (v, sem:sems)
99 --         return v
100 --
101 --     dupSkipChan :: SkipChan a -> IO (SkipChan a)
102 --     dupSkipChan (SkipChan main _) = do
103 --         sem <- newEmptyMVar
104 --         (v, sems) <- takeMVar main
105 --         putMVar main (v, sem:sems)
106 --         return (SkipChan main sem)
107 -- @
108 --
109 -- This example was adapted from the original Concurrent Haskell paper.
110 -- For more examples of 'MVar's being used to build higher-level
111 -- synchronization primitives, see 'Control.Concurrent.Chan' and
112 -- 'Control.Concurrent.QSem'.
113 --
114 -----------------------------------------------------------------------------
115
116 module Control.Concurrent.MVar
117         (
118           -- * @MVar@s
119           MVar          -- abstract
120         , newEmptyMVar  -- :: IO (MVar a)
121         , newMVar       -- :: a -> IO (MVar a)
122         , takeMVar      -- :: MVar a -> IO a
123         , putMVar       -- :: MVar a -> a -> IO ()
124         , readMVar      -- :: MVar a -> IO a
125         , swapMVar      -- :: MVar a -> a -> IO a
126         , tryTakeMVar   -- :: MVar a -> IO (Maybe a)
127         , tryPutMVar    -- :: MVar a -> a -> IO Bool
128         , isEmptyMVar   -- :: MVar a -> IO Bool
129         , withMVar      -- :: MVar a -> (a -> IO b) -> IO b
130         , modifyMVar_   -- :: MVar a -> (a -> IO a) -> IO ()
131         , modifyMVar    -- :: MVar a -> (a -> IO (a,b)) -> IO b
132 #ifndef __HUGS__
133         , addMVarFinalizer -- :: MVar a -> IO () -> IO ()
134 #endif
135     ) where
136
137 #ifdef __HUGS__
138 import Hugs.ConcBase ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
139                   tryTakeMVar, tryPutMVar, isEmptyMVar,
140                 )
141 #endif
142
143 #ifdef __GLASGOW_HASKELL__
144 import GHC.MVar ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
145                   tryTakeMVar, tryPutMVar, isEmptyMVar, addMVarFinalizer
146                 )
147 #endif
148
149 #ifdef __GLASGOW_HASKELL__
150 import GHC.Base
151 #else
152 import Prelude
153 #endif
154
155 import Control.Exception.Base
156
157 {-|
158   This is a combination of 'takeMVar' and 'putMVar'; ie. it takes the value
159   from the 'MVar', puts it back, and also returns it.  This function
160   is atomic only if there are no other producers (i.e. threads calling
161   'putMVar') for this 'MVar'.
162 -}
163 readMVar :: MVar a -> IO a
164 readMVar m =
165   mask_ $ do
166     a <- takeMVar m
167     putMVar m a
168     return a
169
170 {-|
171   Take a value from an 'MVar', put a new value into the 'MVar' and
172   return the value taken. This function is atomic only if there are
173   no other producers for this 'MVar'.
174 -}
175 swapMVar :: MVar a -> a -> IO a
176 swapMVar mvar new =
177   mask_ $ do
178     old <- takeMVar mvar
179     putMVar mvar new
180     return old
181
182 {-|
183   'withMVar' is an exception-safe wrapper for operating on the contents
184   of an 'MVar'.  This operation is exception-safe: it will replace the
185   original contents of the 'MVar' if an exception is raised (see
186   "Control.Exception").  However, it is only atomic if there are no
187   other producers for this 'MVar'.
188 -}
189 {-# INLINE withMVar #-}
190 -- inlining has been reported to have dramatic effects; see
191 -- http://www.haskell.org//pipermail/haskell/2006-May/017907.html
192 withMVar :: MVar a -> (a -> IO b) -> IO b
193 withMVar m io =
194   mask $ \restore -> do
195     a <- takeMVar m
196     b <- restore (io a) `onException` putMVar m a
197     putMVar m a
198     return b
199
200 {-|
201   An exception-safe wrapper for modifying the contents of an 'MVar'.
202   Like 'withMVar', 'modifyMVar' will replace the original contents of
203   the 'MVar' if an exception is raised during the operation.  This
204   function is only atomic if there are no other producers for this
205   'MVar'.
206 -}
207 {-# INLINE modifyMVar_ #-}
208 modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
209 modifyMVar_ m io =
210   mask $ \restore -> do
211     a  <- takeMVar m
212     a' <- restore (io a) `onException` putMVar m a
213     putMVar m a'
214
215 {-|
216   A slight variation on 'modifyMVar_' that allows a value to be
217   returned (@b@) in addition to the modified value of the 'MVar'.
218 -}
219 {-# INLINE modifyMVar #-}
220 modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
221 modifyMVar m io =
222   mask $ \restore -> do
223     a      <- takeMVar m
224     (a',b) <- restore (io a) `onException` putMVar m a
225     putMVar m a'
226     return b