Simple monads
Mark Carroll
mark@chaos.x-philes.com
Thu, 26 Jun 2003 14:40:51 -0400 (EDT)
Not really seeing why Unique is in the IO monad, not deeply understanding
the use of Haskell extensions in the State source, and wanting to try to
learn a bit more about monads, I thought I'd try to write my own monad for
the first time: something for producing a series of unique labels. This is
how it turned out:
==========================================================================
module Label (Label, Labeller, newLabel)
where
import Monad
newtype Label = Label Int deriving (Eq, Ord)
newtype Labeller a = Labeller (Int -> (Int, a))
instance Monad Labeller where
return r = Labeller (\n -> (n, r))
(Labeller g) >>= y =
let f m = let (r, n) = g m
Labeller h = y n
in h r
in Labeller f
newLabel :: Labeller Label
newLabel = Labeller (\n -> (n + 1, Label n))
runLabeller :: Labeller a -> a
runLabeller (Labeller l) = snd (l minBound)
labelTest :: Labeller [Int]
labelTest =
do Label a <- newLabel
Label b <- newLabel
Label c <- newLabel
Label d <- newLabel
return [a,b,c,d]
main = print (runLabeller labelTest)
==========================================================================
I was thinking that maybe,
(a) People could point out to me where I'm still confused, as revealed by
my code. Is it needlessly complicated?
(b) My code may be instructive to someone else.
-- Mark