Skip to content

Instantly share code, notes, and snippets.

@tmhedberg
Last active December 17, 2015 11:49
Show Gist options
  • Save tmhedberg/5605021 to your computer and use it in GitHub Desktop.
Save tmhedberg/5605021 to your computer and use it in GitHub Desktop.
Self-incrementing counters based on mutable references
{-# LANGUAGE FunctionalDependencies #-}
-- | Self-incrementing counters based on mutable references
module Counter where
import Control.Monad.ST
import Data.IORef
import Data.STRef
-- | A class of mutable reference types
--
-- Parameter @r@ is the type of the reference; parameter @m@ is the monad type
-- in which it is embedded.
class Monad m => MutRef r m | r -> m, m -> r where
newMutRef :: a -> m (r a)
readMutRef :: r a -> m a
modifyMutRef :: r a -> (a -> a) -> m ()
instance MutRef IORef IO where newMutRef = newIORef
readMutRef = readIORef
modifyMutRef = modifyIORef
instance MutRef (STRef s) (ST s) where newMutRef = newSTRef
readMutRef = readSTRef
modifyMutRef = modifySTRef
-- | Construct a new counter with the given initial value
makeCounter :: (Enum a, MutRef r m) => a -> m (m a)
makeCounter start = do ct <- newMutRef start
return $ modifyMutRef ct succ >> readMutRef ct
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment