Difference between revisions of "New monads/MonadSupply"

From HaskellWiki
Jump to navigation Jump to search
m
(copyright issue)
Line 1: Line 1:
  +
{{Template:Non-standard copyright}}
 
[[Category:Code]]
 
[[Category:Code]]
 
From New monads, copied from [http://haskell.org/hawiki/MonadSupply old wiki]
 
From New monads, copied from [http://haskell.org/hawiki/MonadSupply old wiki]
 
= MonadSupply =
 
 
   
 
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.
 
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.

Revision as of 03:34, 5 November 2006

This page contains a non-standard copyright. All contributions to HaskellWiki are considered to be released under a simple permissive license (see HaskellWiki:Copyrights for details). Please either remove the material or change the copyright.


From New monads, copied from old wiki

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.

"CaleGibbard/BSDLicense"

{-# OPTIONS_GHC -fglasgow-exts #-}

module MonadSupply 
    (SupplyT,
     MonadSupply,
     supply,
     Supply,
     evalSupplyT,
     evalSupply,
     runSupplyT,
     runSupply)
    where
import Control.Monad
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 Maybe 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