module Reactor.MSem(
MSem,
newMSem,
synchronizeWithChoice,
) where
import Data.IORef
import Control.Concurrent
import Util.Computation
import Events.Synchronized
import Reactor.Lock
import Reactor.BSem
data MSem = MSem {
lock :: BSem,
holdingThreadRef :: IORef (Maybe ThreadId)
}
newMSem :: IO MSem
newMSem =
do
lock <- newBSem
holdingThreadRef <- newIORef Nothing
return (MSem {lock = lock,holdingThreadRef = holdingThreadRef})
synchronizeWithChoice :: MSem -> (Bool -> IO a) -> IO a
synchronizeWithChoice mSem toAct =
do
holdingThreadOpt <- readIORef (holdingThreadRef mSem)
thisThread <- myThreadId
let
heldByUs = case holdingThreadOpt of
Nothing -> False
Just holdingThread -> holdingThread == thisThread
if heldByUs
then
(toAct True)
else
do
acquire (lock mSem)
writeIORef (holdingThreadRef mSem) (Just thisThread)
actOut <- try (toAct False)
writeIORef (holdingThreadRef mSem) Nothing
release (lock mSem)
propagate actOut
instance Synchronized MSem where
synchronize mSem act = synchronizeWithChoice mSem (const act)