Difference between revisions of "New monads/MonadUnique"

From HaskellWiki
Jump to navigation Jump to search
m
 
Line 40: Line 40:
 
evalUniqueT (UniqueT s) = evalStateT s 0
 
evalUniqueT (UniqueT s) = evalStateT s 0
 
evalUnique (Unique s) = runIdentity (evalUniqueT s)
 
evalUnique (Unique s) = runIdentity (evalUniqueT s)
  +
</haskell>
  +
  +
== 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:
  +
  +
[http://haskell.org/hawiki/CaleGibbard_2fBSDLicense "CaleGibbard/BSDLicense"]
  +
  +
<haskell>
  +
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
  +
</haskell>
  +
  +
A test example:
  +
  +
<haskell>
  +
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)
 
</haskell>
 
</haskell>

Revision as of 23:36, 24 August 2006

From NewMonads, copied from old wiki.

MonadUnique

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

"CaleGibbard/BSDLicense"

{-# 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:

"CaleGibbard/BSDLicense"

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)