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

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Sat Dec 30 10:25:35 EST 2006


>> 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]
>
> 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!).

Well, I am pretty scared because the intended functionality is provided
by good old MonadWriter:

    output x = tell [x]

    streamDemo :: Writer [Integer] ()
    streamDemo = do
        tell 1
        tell 2
        tell 5

    execWriter streamDemo == [1,2,5]

assuming an (instance Monoid [a] where ..)


If you want the "stream based" implementation for lists, as

>> type StreamFunc s r = forall b. b -> (b -> s -> b) -> (r,b)

suggests, you can always use a (Writer (List a) c) with the following
Monoid implementation:

    newtype List a = List (forall b . b -> (b -> a -> b) -> b)

    instance Monoid (List a) where
       mempty = List (curry fst)
       f `mappend` g = \one succ -> f (g one succ) succ

I think that the types (StreamFunc s r) and (Writer (List s) r) are
isomorphic (modulo some _|_).


>> 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?

Last but not least, you can simulate foldr with foldl

   foldr f b xs = foldl (\b' x -> b' . f x) id xs b

and vice versa. This is an implementation of difference lists,
essentially a continuation passing style. Personally, I prefer the word
'dual' because one passes from b to it's dual (b -> r) for suitable r.

Unfortunately, the translation

  makelist m = runm' (:) []
      where
      runm' f b = (run m) id (\b' x -> b' . f x) b

does not work on infinite lists because foldl does not return a result
before the whole list is traversed, "tail recursion" is to be blamed.
You should give "run" the meaning of (foldr) and not that of (foldl) as
the latter can be recovered from the former but not the other way round.


Regards,
apfelmus



More information about the Haskell mailing list