[Haskell] Control.Monad.Writer as Python generator

ChrisK chrisk at MIT.EDU
Tue Apr 12 23:09:36 EDT 2005


Hi,

I was thinking to myself:
What in Haskell would give me a "yield" command like a Python generator?

And the answer was "tell" in Control.Monad.Writer -- and I wrote some  
simple examples (see below).

Most Python code using yield would be translated to something much more  
idiomatic in Haskell than using Writer, or to something more  
complicated if it needed IO.

I thought this interesting enough to put on the haskell mailing list  
and wiki since it seemed to be in neither place (I searched, but your  
searching may be better than mine).

If there are no objections then I'll put this example on the wiki; any  
suggestions where on wiki to place it (e.g. MonadWriter)?

=== CUT HERE ===

import Control.Monad.Writer
-- Some type signatures would need -fglasgow-exts to compile

-- We only care about the Writer output, not the function return value
asGenerator :: Writer [a] v -> [a]
asGenerator writer = values where (_,values) = runWriter writer

--yield :: (MonadWriter [a] m) => a -> m ()
yield x = tell [x]

-- This allows several items to be yielded with one command
--yieldMany :: (MonadWriter [a] m) => [a] -> m ()
yieldMany = tell

zeros :: [Integer]
zeros = asGenerator (do yield 0
                         yield 0
                         yield 0)

zerosInf :: [Integer]
zerosInf = asGenerator zeros'
     where zeros' = (yield 0 >>zeros')

-- The Collatz sequence function
foo :: (Integral a) => a -> a
foo x = case (x `mod` 2) of
          0 -> x `div` 2
          1 -> (3*x+1)

-- Uses "return ()" to end the list when 1 is reached
--collatzW :: (MonadWriter [a] m, Integral a) => a -> m ()
collatzW x = do
                yield x
                case x of
                  1 -> return ()
                  _ -> collatzW (foo x)

-- Keeps going, will repeat "1,4,2,1,.." if 1 is reached
--collatzInfW :: (MonadWriter [a] m, Integral a) => a -> m t
collatzInfW x = do
                   yield x
                   collatzInfW (foo x)

--collatzGen :: (MonadWriter [a] (Writer [a]), Integral a) => a -> [a]
collatzGen x = asGenerator (collatzW x)

--collatzInfGen :: (MonadWriter [a] (Writer [a]), Integral a) => a ->  
[a]
collatzInfGen x = asGenerator (collatzInfW x)

-- And these can be combined
collatz1 x = asGenerator (collatzW x >> yield 0 >> collatzW (x+1))

=== CUT HERE ===

*Main> zeros
[0,0,0]

*Main> take 10 zerosInf
[0,0,0,0,0,0,0,0,0,0]

*Main> collatzGen 13
[13,40,20,10,5,16,8,4,2,1]

*Main> take 100 $ collatzInfGen 13
[13,40,20,10,5,16,8,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2, 
1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2, 
1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1]

*Main> collatz1 12
[12,6,3,10,5,16,8,4,2,1,0,13,40,20,10,5,16,8,4,2,1]



More information about the Haskell mailing list