[Haskell-cafe] Shared/Exclusive Locks
Chris Kuklewicz
haskell at list.mightyreason.com
Wed Dec 28 12:28:28 EST 2005
>>
>> STM or IO ?
>>
>> You need a count of shared locks "S", *Var Word32.
>>
>> To increase the count "S", you need to hold a mutex "E", *Var ().
>> So (take mutex "E" >> increment "S" >> release "E") is the the combined
>> operation.
>>
>> To decrease the count "S", you do not need to hold a mutex.
>> (decrement "S").
>>
>> By grabbing the mutex "E" and waiting for "S" to go to zero, you have
>> acquired exclusive control. When you are done just release "E".
>>
>> --
>> Chris
>
>
> This seems fine for STM because you can just retry until count is 0,
> but I don't know of a good way to wait for an MVar to have a particular
> value (I assume busy-wait isn't what you have in mind). You'll
> probably need an additional MVar that exclusive lockers "take" to let
> them block. Then you need to be sure that this MVar is filled when
> count goes to 0 and empty when count goes above zero.
>
>
> Rob Dockins
You are right. I spent too much time teaching myself STM, and I
defaulted to those primatives.
But STM, wrapped in small pieces, makes for interesting IO commands
(untested):
createLocks = do me <- newMVar ()
tv <- atomically $ newTVar (0::Word32)
return (me,tv)
waitForZero :: (Num a, Ord a) => (TVar a) -> IO ()
waitForZero tv = atomically $ do
v <- readTVar tv
when (v>0) retry
takeExclusive :: MVar () -> TVar Word 32 -> IO ()
takeExclusive me tv = takeMVar me >> waitForZero tv
releaseExclusive me = putMVar me ()
takeShared :: MVar () -> TVar Word32 -> IO ()
takeShared me tv = withMVar me $ atomically $ do
v <- readTVar tv
writeTVar tv (v+1)
releaseShared tv = atomically $ do
v <- readTVar tv
writeTVar tv (v-1)
So you don't need much STM to have the benefit of retry. Also: The
ability to put (STM a) or (IO a) into a TVar or MVar makes for wonderful
cross thread solutions to some of the standard synchronization problems.
--
Chris Kuklewicz
More information about the Haskell-Cafe
mailing list