Broken beyond repair: Control.Concurrent.SampleVar

Felipe Lessa felipe.lessa at gmail.com
Sun Apr 12 11:17:33 EDT 2009


Why not

> import Control.Applicative
> import Control.Concurrent.MVar
> import Control.Exception
>
> data SampleVar a = SV {svLock :: MVar (),
>                        svData :: MVar a}
>
> newEmptySampleVar :: IO (SampleVar a)
> newEmptySampleVar = SV <$> newMVar () <$> newEmptyMVar
>
> newSampleVar :: a -> IO (SampleVar a)
> newSampleVar x = SV <$> newMVar () <$> newMVar x
>
> emptySampleVar :: SampleVar a -> IO ()
> emptySampleVar = (>> return ()) . tryTakeMVar . svData
>
> readSampleVar :: SampleVar a -> IO a
> readSampleVar = takeMVar . svData
>
> isEmptySampleVar :: SampleVar a -> IO Bool
> isEmptySampleVar = isEmptyMVar . svData
>
> writeSampleVar :: SampleVar a -> a -> IO ()
> writeSampleVar s x = block $ withMVar (svLock s) $ const $ do
>   tryTakeMVar (svData s)
>   putMVar (svData s) x

?

--
Felipe.


More information about the Libraries mailing list