{-# LANGUAGE MultiParamTypeClasses #-} {- | Module : $Header$ Description : Class connecting mutable variables and monads they exists in. Copyright : (c) Maciej Piechotka License : MIT Stability : none Portability : portable Reference is class which generalizes references and monads they exists in. It means that IORef, STRef and others can be accessed by common interface. -} module Data.Reference ( Reference(..), ) where import Control.Concurrent.MVar import Control.Concurrent.STM import Control.Monad.ST import Data.IORef import Data.STRef -- | Class connecting mutable variable and monad it exists in. class Monad m => Reference r m where -- | Create new reference. newRef :: a -- ^ An initial value -> m (r a) -- | Reads a reference. readRef :: r a -- ^ Reference -> m a -- | Write to reference. writeRef :: r a -- ^ Reference -> a -- ^ New value -> m () -- | Modify the reference. Default implementation is provided but it MUST -- be overloaded if the reference is atomic to provide an atomic write. modifyRef :: r a -- ^ Reference -> (a -> m (a, b)) -- ^ Computation -> m b -- ^ Result of computation modifyRef r f = readRef r >>= f >>= \(a, b) -> writeRef r a >> return b instance Reference IORef IO where newRef = newIORef readRef = readIORef writeRef = writeIORef instance Reference (STRef s) (ST s) where newRef = newSTRef readRef = readSTRef writeRef = writeSTRef instance Reference MVar IO where newRef = newMVar readRef = readMVar writeRef = putMVar modifyRef = modifyMVar instance Reference TVar STM where newRef = newTVar readRef = readTVar writeRef = writeTVar