module Data.MRef.Instances
( MVar
, MonadIO(..)
#ifdef useSTM
, module Data.MRef.Instances.STM
#endif
) where
#ifdef useSTM
import Data.MRef.Instances.STM
#endif
import Data.MRef.Types
import Control.Concurrent.MVar
import Control.Monad.Trans
instance HasMRef IO where
newMRef x = fmap MRef (newMVar x)
newEmptyMRef = fmap MRef newEmptyMVar
instance MonadIO m => NewMRef (MVar a) m a where
newMReference = liftIO . newMVar
newEmptyMReference = liftIO newEmptyMVar
instance MonadIO m => TakeMRef (MVar a) m a where
takeMReference = liftIO . takeMVar
instance MonadIO m => PutMRef (MVar a) m a where
putMReference r = liftIO . putMVar r