New monads/MonadSupply

From HaskellWiki
< New monads
Revision as of 05:09, 4 April 2014 by GaneshSittampalam (talk | contribs) (fix import)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
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.


Here is a simple monad/monad transformer for computations which consume values from a (finite or infinite) supply. Note that due to pattern matching, running out of supply in a non-MonadZero monad will cause an error.

{-# OPTIONS_GHC -fglasgow-exts #-}

module MonadSupply 
    (SupplyT,
     MonadSupply,
     supply,
     Supply,
     evalSupplyT,
     evalSupply,
     runSupplyT,
     runSupply)
    where
import Control.Monad
import Control.Monad.Identity
import Control.Monad.State

newtype SupplyT s m a = SupplyT (StateT [s] m a)
    deriving (Functor, Monad, MonadTrans, MonadIO)

newtype Supply s a = Supply (SupplyT s Identity a)
    deriving (Functor, Monad, MonadSupply s)

class Monad m => MonadSupply s m | m -> s where
    supply :: m s
    
instance Monad m => MonadSupply s (SupplyT s m) where
    supply = SupplyT $ do
                (x:xs) <- get
                put xs
                return x

evalSupplyT (SupplyT s) supp = evalStateT s supp
evalSupply (Supply s) supp = evalSupplyT s supp

runSupplyT (SupplyT s) supp = runStateT s supp
runSupply (Supply s) supp = runSupplyT s supp

As an example, if we want to supply unique strings for use as variable names, the following specialisation of runSupply (or its obvious analogue with runSupplyT) might be handy:

runSupplyVars x = runSupply x vars
    where vars = [replicate k ['a'..'z'] | k <- [1..]] >>= sequence