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

Iavor Diatchki iavor.diatchki at gmail.com
Sun Dec 31 14:52:51 EST 2006


hi,
you might find the "backward" state monad interesting.  here is the basic idea:
newtype S s a = S (s -> (a,s))

instance Monad (S s) where
  return a   = S (\s -> (a,s))
  S m >>= k  = S (\s1 -> let (a,s3) = m s2
                             (b,s2) = run s1 (k a)
                         in (b,s3))

put x = S (\s -> ((),x:s))


run s (S m) = m s

test = snd $ run []
     $ do put 'x'
          put 'y'
          undefined


hope this helps
-iavor



On 12/30/06, Ryan Ingram <ryani.spam at gmail.com> 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
>
> Thanks,
>   -- ryan
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>
>


More information about the Haskell mailing list