New monads/MonadUnique

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

From New monads, copied from old wiki.

This is a simple (trivial) monad transformer for supplying unique integer values to an algorithm.

MonadUnique

{-# OPTIONS_GHC -fglasgow-exts #-}

module MonadUnique
        ( UniqueT,
          Unique,
          MonadUnique,
          fresh,
          evalUniqueT,
          evalUnique )
    where

import Control.Monad
import Control.Monad.State
import Control.Monad.Identity

newtype UniqueT m a = UniqueT (StateT Integer m a)
    deriving (Functor, Monad, MonadTrans, MonadIO)

newtype Unique a = Unique (UniqueT Identity a)
    deriving (Functor, Monad, MonadUnique)

class Monad m => MonadUnique m where
    fresh :: m Integer

instance (Monad m) => MonadUnique (UniqueT m) where
    fresh = UniqueT $ do
                n <- get
                put (succ n)
                return n

evalUniqueT (UniqueT s) = evalStateT s 0
evalUnique (Unique s) = runIdentity (evalUniqueT s)

STSupply

There is also a simple way to get the same functionality in the ST Monad. Here's a quick module to construct infinite supplies of unique values in the ST monad:

module STSupply (Unique, createSupply) where

import Control.Monad.ST
import Data.STRef

newtype Unique = Unique Integer deriving (Eq, Ord)

createSupply :: ST s (ST s Unique)
createSupply = do
    v <- newSTRef $ Unique 0
    return $ do
        Unique x <- readSTRef v
        writeSTRef v $ Unique (x+1)
        return $ Unique x

A test example:

import Control.Monad.ST
import STSupply

main = print test1

test1 = runST supplyTest
    where supplyTest = do
              fresh <- createSupply
              x <- fresh
              y <- fresh
              return (x == x, x == y, x < y)