SampleVar semantics
Bas van Dijk
v.dijk.bas at gmail.com
Sun Jan 2 21:58:54 CET 2011
Wouldn't the following implementation of SampleVars be simpler (and
slightly more efficient) that the current one?
The difference is that instead of keeping an Int that represents the
number of readers, I keep a Bool that represents whether the SampleVar
is empty.
While your example runs without deadlocking, I haven't yet fully
checked the correctness though...
-----------------------------------------------------------------------------
-- |
-- Module : Control.Concurrent.SampleVar
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer : libraries at haskell.org
-- Stability : experimental
-- Portability : non-portable (concurrency)
--
-- Sample variables
--
-----------------------------------------------------------------------------
module Control.Concurrent.SampleVar
(
-- * Sample Variables
SampleVar, -- :: type _ =
newEmptySampleVar, -- :: IO (SampleVar a)
newSampleVar, -- :: a -> IO (SampleVar a)
emptySampleVar, -- :: SampleVar a -> IO ()
readSampleVar, -- :: SampleVar a -> IO a
writeSampleVar, -- :: SampleVar a -> a -> IO ()
isEmptySampleVar, -- :: SampleVar a -> IO Bool
) where
import Prelude
import Control.Concurrent.MVar
import Control.Exception ( mask_ )
import Data.Functor ( (<$>) )
-- |
-- Sample variables are slightly different from a normal 'MVar':
--
-- * Reading an empty 'SampleVar' causes the reader to block.
-- (same as 'takeMVar' on empty 'MVar')
--
-- * Reading a filled 'SampleVar' empties it and returns value.
-- (same as 'takeMVar')
--
-- * Writing to an empty 'SampleVar' fills it with a value, and
-- potentially, wakes up a blocked reader (same as for 'putMVar' on
-- empty 'MVar').
--
-- * Writing to a filled 'SampleVar' overwrites the current value.
-- (different from 'putMVar' on full 'MVar'.)
newtype SampleVar a = SampleVar ( MVar ( Bool -- is empty?
, MVar a
)
)
deriving (Eq)
-- |Build a new, empty, 'SampleVar'
newEmptySampleVar :: IO (SampleVar a)
newEmptySampleVar = do
v <- newEmptyMVar
SampleVar <$> newMVar (True, v)
-- |Build a 'SampleVar' with an initial value.
newSampleVar :: a -> IO (SampleVar a)
newSampleVar a = do
v <- newMVar a
SampleVar <$> newMVar (False, v)
-- |If the SampleVar is full, leave it empty. Otherwise, do nothing.
emptySampleVar :: SampleVar a -> IO ()
emptySampleVar (SampleVar svar) = mask_ $ do
s@(empty, val) <- takeMVar svar
if empty
then putMVar svar s
else takeMVar val >> putMVar svar (True, val)
-- |Wait for a value to become available, then take it and return.
readSampleVar :: SampleVar a -> IO a
readSampleVar (SampleVar svar) = mask_ $ do
--
-- filled => make empty and grab sample
-- not filled => try to grab value, empty when read val.
--
s@(empty, val) <- takeMVar svar
if empty
then putMVar svar s
else putMVar svar (True, val)
takeMVar val
-- |Write a value into the 'SampleVar', overwriting any previous value that
-- was there.
writeSampleVar :: SampleVar a -> a -> IO ()
writeSampleVar (SampleVar svar) v = mask_ $ do
--
-- filled => overwrite
-- not filled => fill, write val
--
s@(empty, val) <- takeMVar svar
if empty
then do
putMVar val v
putMVar svar (False, val)
else do
swapMVar val v
putMVar svar s
-- | Returns 'True' if the 'SampleVar' is currently empty.
--
-- Note that this function is only useful if you know that no other
-- threads can be modifying the state of the 'SampleVar', because
-- otherwise the state of the 'SampleVar' may have changed by the time
-- you see the result of 'isEmptySampleVar'.
--
isEmptySampleVar :: SampleVar a -> IO Bool
isEmptySampleVar (SampleVar svar) = fst <$> readMVar svar
-----------------------------------------------------------------------------
Regards,
Bas
More information about the Libraries
mailing list