{-# LANGUAGE DeriveDataTypeable #-} ------------------------------------------------------------------------------- -- | -- Module : Data.IORRef -- Copyright : (c) Ivan Tomac 2008 -- License : BSD3 -- -- Maintainer : tomac `at` pacific `dot` net `dot` au -- Stability : experimental -- -- Mutable references in the IOR monad. -- ------------------------------------------------------------------------------- module Data.IORRef ( IORRef , newIORRef , readIORRef , writeIORRef , modifyIORRef ) where import Control.Monad.Trans import Data.Generics import Data.IORef import System.IOR -- | A value of type @'IORRef' r a@ is a mutable variable in region @r@, -- containing a value of type @a@. newtype IORRef r a = IORRef { unIORRef :: IORef a } deriving (Data, Eq, Typeable) -- | Create a new 'IORRef' in region @r@. newIORRef :: a -> IOR r rs (IORRef r a) newIORRef = liftIO . fmap IORRef . newIORef -- | Read the value of an 'IORRef'. readIORRef :: RElem r' rs => IORRef r' a -> IOR r rs a readIORRef = liftIO . readIORef . unIORRef -- | Write a new value into an 'IORRef'. writeIORRef :: RElem r' rs => IORRef r' a -> a -> IOR r rs () writeIORRef = (liftIO .) . writeIORef . unIORRef -- | Mutate the contents of an 'IORRef'. modifyIORRef :: RElem r' rs => IORRef r' a -> (a -> a) -> IOR r rs () modifyIORRef = (liftIO .) . modifyIORef . unIORRef