Hi,

you'll need to loosen up your data dependencies a little.
Consider the following expression,

   let action = a1 >> a2 >> ... >> an in runI action

'runI' forces the evaluation of an IState, which according
to your (>>=) defn, action's IState will be the one that 'an'
evaluates to/returns.

Hence, in your particular example, you won't see any output
until 'an' has been evaluated ==> no output will appear until
the end of the input has been seen.

One way out is to define (>>=) as follows:

   (I c1) >>= fc2 = I $ \s0 -> 
           let (r,s1)   = c1 s0
               (I c2)   = fc2 r
                   (r2, s2) = c2 (s1{io=return ()})
             in
             (r2, IState { io = io s1 >> io s2})

or, redefine your monad to distinguish between output &
the (threaded) interaction state.

hth
--sigbjorn


> -----Original Message-----
> From: Sengan [mailto:[EMAIL PROTECTED]]
> Sent: Thursday, August 10, 2000 16:54
> To: [EMAIL PROTECTED]
> Subject: Why is the following not lazy?
> 
> 
> I'm writing a program that involves the use of an interaction
> Monad. However it seems to be insufficiently lazy to provide
> any interaction. The following code is derived from my original
> but highly simplified. Why is "works" lazy, but "main" is not?
> 
> Thanks for any help
> 
> Sengan
> 
> > module Main(main) where
> > import IO
> 
> --------------------------------------------------------------
> ------------------
> 
> > works
> >   = hGetContents stdin >>= \input ->
> >     foldr (>>) (return ()) $ map putStr $ lines input
> 
> --------------------------------------------------------------
> ------------------
> 
> > main
> >   = hGetContents stdin >>= \input ->
> >     runI $ foldr (>>) (return "") $ map output $ lines input
> 
> > data IState = IState { io             :: IO () }
> 
> > data I a    = I (IState -> (a, IState))
> 
> > instance Monad I where
> >    return k       = I $ \s  -> (k,s)
> >    (I c1) >>= fc2 = I $ \s0 -> let (r,s1) = c1 s0
> >                                    I c2   = fc2 r in
> >                                c2 s1
> 
> > runI (I c) = let (result, state) = c (IState $ return ()) in
> >              io state >> return ()
> 
> > output string
> >   = I $ \s -> (string, s { io = (io s) >> putStr (string ++ "\n") })
> 

Reply via email to