File: ReadWriteLock.hs

package info (click to toggle)
haskell-concurrent-extra 0.7.0.12-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 184 kB
  • sloc: haskell: 1,040; makefile: 6
file content (352 lines) | stat: -rw-r--r-- 11,590 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
{-# LANGUAGE CPP
           , DeriveDataTypeable
           , NamedFieldPuns
           , NoImplicitPrelude
  #-}

#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#endif

-------------------------------------------------------------------------------
-- |
-- Module     : Control.Concurrent.ReadWriteLock
-- Copyright  : (c) 2010-2011 Bas van Dijk & Roel van Dijk
-- License    : BSD3 (see the file LICENSE)
-- Maintainer : Bas van Dijk <v.dijk.bas@gmail.com>
--            , Roel van Dijk <vandijk.roel@gmail.com>
--
-- Multiple-reader, single-writer locks. Used to protect shared resources which
-- may be concurrently read, but only sequentially written.
--
-- All functions are /exception safe/. Throwing asynchronous exceptions will not
-- compromise the internal state of an 'RWLock'. This means it is perfectly safe
-- to kill a thread that is blocking on, for example, 'acquireRead'.
--
-- See also Java's version:
-- <http://java.sun.com/javase/7/docs/api/java/util/concurrent/locks/ReadWriteLock.html>
--
-- This module is designed to be imported qualified. We suggest importing it
-- like:
--
-- @
-- import           Control.Concurrent.ReadWriteLock        ( RWLock )
-- import qualified Control.Concurrent.ReadWriteLock as RWL ( ... )
-- @
--
-------------------------------------------------------------------------------

module Control.Concurrent.ReadWriteLock
  ( RWLock

    -- *Creating Read-Write Locks
  , new
  , newAcquiredRead
  , newAcquiredWrite

    -- *Read access
    -- **Blocking
  , acquireRead
  , releaseRead
  , withRead
  , waitRead
    -- **Non-blocking
  , tryAcquireRead
  , tryWithRead

    -- *Write access
    -- **Blocking
  , acquireWrite
  , releaseWrite
  , withWrite
  , waitWrite
    -- **Non-blocking
  , tryAcquireWrite
  , tryWithWrite
  ) where


-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

-- from base:
import Control.Applicative     ( liftA2, liftA3 )
import Control.Concurrent.MVar ( MVar, newMVar, takeMVar, putMVar )
import Control.Exception       ( bracket_, onException )
import Control.Monad           ( return, (>>) )
import Data.Bool               ( Bool(False, True) )
import Data.Eq                 ( Eq, (==) )
import Data.Function           ( ($), (.), on )
import Data.Int                ( Int )
import Data.Maybe              ( Maybe(Nothing, Just) )
import Data.List               ( (++))
import Data.Typeable           ( Typeable )
import Prelude                 ( String, ($!), succ, pred, error )
import System.IO               ( IO )

#if __GLASGOW_HASKELL__ < 700
import Prelude                 ( fromInteger )
import Control.Monad           ( (>>=), fail )
#endif

-- from concurrent-extra (this package):
import           Control.Concurrent.Lock ( Lock )
import qualified Control.Concurrent.Lock as Lock
    ( new, newAcquired, acquire, release, wait )

import Utils ( mask, mask_ )


-------------------------------------------------------------------------------
-- Read Write Lock
-------------------------------------------------------------------------------

{-|
Multiple-reader, single-writer lock. Is in one of three states:

* \"Free\": Read or write access can be acquired without blocking.

* \"Read\": One or more threads have acquired read access. Blocks write access.

* \"Write\": A single thread has acquired write access. Blocks other threads
from acquiring both read and write access.
-}
data RWLock = RWLock { state     :: MVar State
                     , readLock  :: Lock
                     , writeLock :: Lock
                     } deriving Typeable

instance Eq RWLock where
    (==) = (==) `on` state

-- | Internal state of the 'RWLock'.
data State = Free | Read Int | Write


-------------------------------------------------------------------------------
-- * Creating Read-Write Locks
-------------------------------------------------------------------------------

-- | Create a new 'RWLock' in the \"free\" state; either read or write access
-- can be acquired without blocking.
new :: IO RWLock
new = liftA3 RWLock (newMVar Free)
                    Lock.new
                    Lock.new

-- | Create a new 'RWLock' in the \"read\" state; only read can be acquired
-- without blocking.
newAcquiredRead :: IO RWLock
newAcquiredRead = liftA3 RWLock (newMVar $ Read 1)
                                Lock.newAcquired
                                Lock.new

-- | Create a new 'RWLock' in the \"write\" state; either acquiring read or
-- write will block.
newAcquiredWrite :: IO RWLock
newAcquiredWrite = liftA3 RWLock (newMVar Write)
                                 Lock.new
                                 Lock.newAcquired


-------------------------------------------------------------------------------
-- * Read access
-------------------------------------------------------------------------------

{-|
Acquire the read lock.

Blocks if another thread has acquired write access. If @acquireRead@ terminates
without throwing an exception the state of the 'RWLock' will be \"read\".

Implementation note: Throws an exception when more than (maxBound :: Int)
simultaneous threads acquire the read lock. But that is unlikely.
-}
acquireRead :: RWLock -> IO ()
acquireRead (RWLock {state, readLock, writeLock}) = mask_ acqRead
    where
      acqRead = do st <- takeMVar state
                   case st of
                     Free   -> do Lock.acquire readLock
                                  putMVar state $ Read 1
                     Read n -> putMVar state . Read $! succ n
                     Write  -> do putMVar state st
                                  Lock.wait writeLock
                                  acqRead

{-|
Try to acquire the read lock; non blocking.

Like 'acquireRead', but doesn't block. Returns 'True' if the resulting state is
\"read\", 'False' otherwise.
-}
tryAcquireRead :: RWLock -> IO Bool
tryAcquireRead (RWLock {state, readLock}) = mask_ $ do
  st <- takeMVar state
  case st of
    Free   -> do Lock.acquire readLock
                 putMVar state $ Read 1
                 return True
    Read n -> do putMVar state . Read $! succ n
                 return True
    Write  -> do putMVar state st
                 return False

{-|
Release the read lock.

If the calling thread was the last one to relinquish read access the state will
revert to \"free\".

It is an error to release read access to an 'RWLock' which is not in the
\"read\" state.
-}
releaseRead :: RWLock -> IO ()
releaseRead (RWLock {state, readLock}) = mask_ $ do
  st <- takeMVar state
  case st of
    Read 1 -> do Lock.release readLock
                 putMVar state Free
    Read n -> putMVar state . Read $! pred n
    _ -> do putMVar state st
            error $ moduleName ++ ".releaseRead: already released"

{-|
A convenience function wich first acquires read access and then performs the
computation. When the computation terminates, whether normally or by raising an
exception, the read lock is released.
-}
withRead :: RWLock -> IO a -> IO a
withRead = liftA2 bracket_ acquireRead releaseRead

{-|
A non-blocking 'withRead'. First tries to acquire the lock. If that fails,
'Nothing' is returned. If it succeeds, the computation is performed. When the
computation terminates, whether normally or by raising an exception, the lock is
released and 'Just' the result of the computation is returned.
-}
tryWithRead :: RWLock -> IO a -> IO (Maybe a)
tryWithRead l a = mask $ \restore -> do
  acquired <- tryAcquireRead l
  if acquired
    then do r <- restore a `onException` releaseRead l
            releaseRead l
            return $ Just r
    else return Nothing

{-|
* When the state is \"write\", @waitRead@ /blocks/ until a call to
'releaseWrite' in another thread changes the state to \"free\".

* When the state is \"free\" or \"read\" @waitRead@ returns immediately.

@waitRead@ does not alter the state of the lock.

Note that @waitRead@ is just a convenience function defined as:

@waitRead l = 'mask_' '$' 'acquireRead' l '>>' 'releaseRead' l@
-}
waitRead :: RWLock -> IO ()
waitRead l = mask_ $ acquireRead l >> releaseRead l


-------------------------------------------------------------------------------
-- *Write access
-------------------------------------------------------------------------------

{-|
Acquire the write lock.

Blocks if another thread has acquired either read or write access. If
@acquireWrite@ terminates without throwing an exception the state of the
'RWLock' will be \"write\".
-}
acquireWrite :: RWLock -> IO ()
acquireWrite (RWLock {state, readLock, writeLock}) = mask_ acqWrite
    where
      acqWrite = do st <- takeMVar state
                    case st of
                      Free   -> do Lock.acquire writeLock
                                   putMVar state Write
                      Read _ -> do putMVar state st
                                   Lock.wait readLock
                                   acqWrite
                      Write  -> do putMVar state st
                                   Lock.wait writeLock
                                   acqWrite

{-|
Try to acquire the write lock; non blocking.

Like 'acquireWrite', but doesn't block. Returns 'True' if the resulting state is
\"write\", 'False' otherwise.
-}
tryAcquireWrite :: RWLock -> IO Bool
tryAcquireWrite (RWLock {state, writeLock}) = mask_ $ do
  st <- takeMVar state
  case st of
    Free   -> do Lock.acquire writeLock
                 putMVar state Write
                 return True
    _      -> do putMVar state st
                 return False

{-|
Release the write lock.

If @releaseWrite@ terminates without throwing an exception the state will be
\"free\".

It is an error to release write access to an 'RWLock' which is not in the
\"write\" state.
-}
releaseWrite :: RWLock -> IO ()
releaseWrite (RWLock {state, writeLock}) = mask_ $ do
  st <- takeMVar state
  case st of
    Write -> do Lock.release writeLock
                putMVar state Free
    _ -> do putMVar state st
            error $ moduleName ++ ".releaseWrite: already released"

{-|
A convenience function wich first acquires write access and then performs
the computation. When the computation terminates, whether normally or by raising
an exception, the write lock is released.
-}
withWrite :: RWLock -> IO a -> IO a
withWrite = liftA2 bracket_ acquireWrite releaseWrite

{-|
A non-blocking 'withWrite'. First tries to acquire the lock. If that fails,
'Nothing' is returned. If it succeeds, the computation is performed. When the
computation terminates, whether normally or by raising an exception, the lock is
released and 'Just' the result of the computation is returned.
-}
tryWithWrite :: RWLock -> IO a -> IO (Maybe a)
tryWithWrite l a = mask $ \restore -> do
  acquired <- tryAcquireWrite l
  if acquired
    then do r <- restore a `onException` releaseWrite l
            releaseWrite l
            return $ Just r
    else return Nothing

{-|
* When the state is \"write\" or \"read\" @waitWrite@ /blocks/ until a call to
'releaseWrite' or 'releaseRead' in another thread changes the state to \"free\".

* When the state is \"free\" @waitWrite@ returns immediately.

@waitWrite@ does not alter the state of the lock.

Note that @waitWrite@ is just a convenience function defined as:

@waitWrite l = 'mask_' '$' 'acquireWrite' l '>>' 'releaseWrite' l@
-}
waitWrite :: RWLock -> IO ()
waitWrite l = mask_ $ acquireWrite l >> releaseWrite l

moduleName :: String
moduleName = "Control.Concurrent.ReadWriteLock"