module MAC.MVar
(
MACMVar
, newMACMVar
, newMACEmptyMVar
, takeMACMVar
, putMACMVar
)
where
import MAC.Lattice
import MAC.MAC
import MAC.Effects
import Control.Concurrent.MVar
type MACMVar l a = Res l (MVar a)
newMACMVar :: Less l l' => a -> MAC l (MACMVar l' a)
newMACMVar = create . newMVar
newMACEmptyMVar :: Less l l' => MAC l (MACMVar l' a)
newMACEmptyMVar = create newEmptyMVar
takeMACMVar :: Less l l => MACMVar l a -> MAC l a
takeMACMVar = rw_read takeMVar
putMACMVar :: Less l l => MACMVar l a -> a -> MAC l ()
putMACMVar secmv v = rw_write (flip putMVar v) secmv