[Haskell] Converting a 'streaming' monad into a list

Lennart Kolmodin kolmodin at dtek.chalmers.se
Sat Dec 30 07:31:36 EST 2006


-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

Ryan Ingram wrote:
> Hi everyone... it's my newbie post!
>  
> I am trying to create a monad which allows computations to output data
> to a stream.  (Probably such a thing already exists, but it's a good
> problem for my current skill level in Haskell)
>  
> For example:
> streamDemo = do
>     output 1
>     output 2
>     output 5
> makelist streamDemo -- [1,2,5]
> I modelled my implementation around the state monad, but with a
> different execution model:
>  
> class (Monad m) => MonadStream w m | m -> w where
>     output :: w -> m ()
>     run :: m a -> s -> (s -> w -> s) -> s  -- basically foldl on the
> stream values
> makelist m = reverse $ run m [] (flip (:))
> 
> -- s is the type of the object to stream, r is the return type
> type StreamFunc s r = forall b. b -> (b -> s -> b) -> (r,b)
> newtype Stream s r = Stream { run' :: StreamFunc s r }
> instance Monad (Stream s) where
>     return r = Stream (\s _ -> (r,s))
>     Stream m >>= k = Stream (\s f -> let (r,s') = (m s f)
>         in run' (k r) s' f)
> instance (MonadStream w) (Stream w) where
>     output w = Stream (\s f -> ((),f s w))
>     run m st f = snd $ run' m st f
>  
> What I don't like is how makelist comes out.  It feels wrong to need to
> use reverse, and that also means that infinite streams completely fail
> to work.  But I think it's impossible to fix with the
> "foldl"-style "run".  Is there a better implementation of
> "makelist" possible with my current definition of "run"?  If not, what
> type should "run" have so that it can work correctly?
>  
> As an example, I want to fix the implementation to make the following
> code work:
> fibs :: Stream Integer ()
> fibs =  fibs' 0 1
>         where fibs' x y = output y >> fibs' y (x+y)
> fiblist :: [Integer] 
> fiblist = makelist fibs
>  
> take 5 fiblist -- [1,1,2,3,5], but currently goes into an infinite loop
>  

As you might have guessed, reversing the list also forces it, thus
making infinite lists impossible and long lists will perform badly.

The trick is when you run the 'output' function to return that element
and _then_ do the rest of the computation. What does this sounds like?
That's right, the continuation monad! :)
It's not as scary as it might sound like, it can basically be
implemented with two one-liner functions (wow!).

I've taken the liberty of writing your monad, except without the classes
and instances:


import Control.Monad.Cont

type Stream r a = Cont [r] a

output :: r -> Stream r ()
output r = Cont $ \c -> r : c ()

makelist :: Stream r () -> [r]
makelist m = runCont m (const [])

fibs :: Num n => Stream n ()
fibs = fibs' 0 1
    where fibs' x y = output x >> fibs' y (x+y)

fiblist :: [Integer]
fiblist = makelist fibs


So, the output function returns its argument, then the result of the
rest of the computation.
makelist provides a stop to the continuation with the empty list.

You recognize fibs and fiblist from your code.

Is this what you where looking for?

You can see the monad transformer version of this technique in the yet
to be released library Binary ByteString:
http://www.haskell.org/~kolmodin/code/bbs/src/Data/ByteString/Binary/EncM.hs

Cheers,
  Lennart Kolmodin
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.5 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFFllwn4txYG4KUCuERAo/UAJ9nXeGnaONCI4BDSn7YZIUFryB0VQCbBJpL
lxw7HG17Yx0aPJXQ12gWPtA=
=IEjs
-----END PGP SIGNATURE-----


More information about the Haskell mailing list