Lazy Evaluation in Monads

I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate: iRecurse :: (Num a) => IO a iRecurse = do recurse <- iRecurse return 1 main = (putStrLn . show) =<< iRecurse Any pointers to a good explanation of when the IO monad is lazy? === The long story === I wrote a function unfold with type signature (([a] -> a) -> [a]), for generating a list in which each element can be calculated from all of the previous elements. unfold :: ([a] -> a) -> [a] unfold f = unfold1 f [] unfold1 :: ([a] -> a) -> [a] -> [a] unfold1 f l = f l : unfold1 f (f l : l) Now I'm attempting to do the same thing, except where f returns a monad. (My use case is when f randomly selects the next element, i.e. text generation from markov chains.) So I want unfoldM1 :: (Monad m) => ([a] -> m a) -> [a] -> m [a] My instinct, then, would be to do something like: unfoldM1 f l = do next <- f l rest <- unfoldM1 f (next : l) return (next : rest) But that, like iRecurse above, doesn't work.

Suppose iRecurse looks like this:
iRecurse = do
x <- launchMissiles
r <- iRecurse
return 1
As x is never needed, launchMissiles will never execute. It obviously is
not what is needed.
But in Haskell, standart file input|output is often lazy. It's a
combination of buffering and special tricks, not the usual rule.
Scott Lawrence
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate:
iRecurse :: (Num a) => IO a iRecurse = do recurse <- iRecurse return 1
main = (putStrLn . show) =<< iRecurse
Any pointers to a good explanation of when the IO monad is lazy?
=== The long story ===
I wrote a function unfold with type signature (([a] -> a) -> [a]), for generating a list in which each element can be calculated from all of the previous elements.
unfold :: ([a] -> a) -> [a] unfold f = unfold1 f []
unfold1 :: ([a] -> a) -> [a] -> [a] unfold1 f l = f l : unfold1 f (f l : l)
Now I'm attempting to do the same thing, except where f returns a monad. (My use case is when f randomly selects the next element, i.e. text generation from markov chains.) So I want
unfoldM1 :: (Monad m) => ([a] -> m a) -> [a] -> m [a]
My instinct, then, would be to do something like:
unfoldM1 f l = do next <- f l rest <- unfoldM1 f (next : l) return (next : rest)
But that, like iRecurse above, doesn't work.

On 05/31/2011 04:20 PM, Artyom Kazak wrote:
Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1
As x is never needed, launchMissiles will never execute. It obviously is not what is needed.
Prelude> let launchMissiles = putStrLn "UH OH" >> return 1 Prelude> let iRecurse = launchMissiles >> return 1 Prelude> iRecurse UH OH 1 Prelude> Looks like launchMissiles /does/ execute, even though x is (obviously) never needed.

No, I think Artyom meant "assuming IO is lazy".
He intended to show that, indeed, it is not, or else side-effects would
never be performed
2011/5/31 Scott Lawrence
On 05/31/2011 04:20 PM, Artyom Kazak wrote:
Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1
As x is never needed, launchMissiles will never execute. It obviously is not what is needed.
Prelude> let launchMissiles = putStrLn "UH OH" >> return 1 Prelude> let iRecurse = launchMissiles >> return 1 Prelude> iRecurse UH OH 1 Prelude>
Looks like launchMissiles /does/ execute, even though x is (obviously) never needed.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tuesday 31 May 2011 22:35:26, Yves Parès wrote:
He intended to show that, indeed, it is not, or else side-effects would never be performed
On the other hand, IO is lazy in the values it produces. Going with the IO a = State RealWorld a fiction, IO is state-strict but value-lazy. The side-effects affect the state, hence are performed, the values are only evaluated to the extent required to determine the state.

Scott Lawrence
On 05/31/2011 04:20 PM, Artyom Kazak wrote:
Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1
As x is never needed, launchMissiles will never execute. It obviously is not what is needed. Prelude> let launchMissiles = putStrLn "UH OH" >> return 1 Prelude> let iRecurse = launchMissiles >> return 1 Prelude> iRecurse UH OH 1 Prelude> Looks like launchMissiles /does/ execute, even though x is (obviously) never needed.
Oh, sorry. I was unclear. I have meant "assuming IO is lazy", as Yves wrote. And saying "some hacks" I meant unsafeInterleaveIO, which lies beneath the laziness of, for example, getContents.

On 05/31/2011 04:48 PM, Artyom Kazak wrote:
Oh, sorry. I was unclear. I have meant "assuming IO is lazy", as Yves wrote.
Ah, ok. That makes more sense.
And saying "some hacks" I meant unsafeInterleaveIO, which lies beneath the laziness of, for example, getContents.
Which explains why assuming getContents is strict has never worked for me. I'm trying to implement unfoldM1 without using unsafeIO, if possible. Since unfoldM1 f l = do next <- f l rest <- unfoldM1 f (next : l) return (next : rest) obviously won't work, I've been trying to use fmap unfoldM1 :: (Functor m, Monad m) => ([a] -> m a) -> [a] -> m [a] unfoldM1 f l = do next <- f l fmap (next :) $ unfoldM1 f (next : l) Evaluation here also doesn't terminate (or, (head $ unfoldM (return . head)) doesn't), although I can't figure out why. fmap shouldn't need to fully evaluate a list to prepend an element, right?

2011/5/31 Scott Lawrence
Evaluation here also doesn't terminate (or, (head $ unfoldM (return . head)) doesn't), although I can't figure out why. fmap shouldn't need to fully evaluate a list to prepend an element, right?
I'm afriad fmap doesn't get to choose - if the monad is strict then both definitions are equivalent (probably...).

Apparently:
Prelude> let r = (fmap (1:) r) :: IO [Integer]
Prelude> fmap (take 5) r
*** Exception: stack overflow
Thanks - I'll just have to stay out of IO for this, then.
On Tue, May 31, 2011 at 17:05, Stephen Tetley
2011/5/31 Scott Lawrence
: Evaluation here also doesn't terminate (or, (head $ unfoldM (return . head)) doesn't), although I can't figure out why. fmap shouldn't need to fully evaluate a list to prepend an element, right?
I'm afriad fmap doesn't get to choose - if the monad is strict then both definitions are equivalent (probably...).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Scott Lawrence

On Tue, May 31, 2011 at 3:49 PM, Scott Lawrence
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate:
iRecurse :: (Num a) => IO a iRecurse = do recurse <- iRecurse return 1
main = (putStrLn . show) =<< iRecurse
Any pointers to a good explanation of when the IO monad is lazy?
import System.IO.Unsafe iRecurse :: (Num a) => IO a iRecurse = do recurse <- unsafeInterleaveIO iRecurse return 1 More interesting variations of this leave you with questions of whether or not the missles were launched, or, worse yet, was data actually read from the file handle? Anthony

On 5/31/11 12:49 PM, Scott Lawrence wrote:
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy.
Whether they are lazy or not depends entirely on the definition of the monad. For example, if you look up the ST and State monads you will find that they come in strict and lazy flavors. As a general rule, operations in the IO monad are strict except for very special cases which are explicitly labeled as such, e.g. unsafeInterleaveIO, lazyIO, etc. FYI, in GHC the definition of IO is at http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-prim-0.2.0.0/src/GH... You can tell it is strict because the result of the map is an unboxed tuple, which is strict (at least, if I understand correctly :-) ). If you are curious, State# and RealWorld are defined here: http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-prim-0.2.0.0/src/GH.... State# and RealWorld do not contain data constructors because they are not intended to contain data but rather to parametrize types --- that is to say, you can think of IO as being a special case of the strict ST transformer which uses a special type tag to keep different ST threads separate (even though this type is never instantiated), and in the case of IO the state tag is RealWorld. So in short, monads need not be strict but often are, and in particular IO is designed to be strict because it is essentially just a special case of the strict ST monad. Cheers, Greg

On Tue, May 31, 2011 at 2:49 PM, Scott Lawrence
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate:
iRecurse :: (Num a) => IO a iRecurse = do recurse <- iRecurse return 1
main = (putStrLn . show) =<< iRecurse
Any pointers to a good explanation of when the IO monad is lazy?
=== The long story ===
I wrote a function unfold with type signature (([a] -> a) -> [a]), for generating a list in which each element can be calculated from all of the previous elements.
unfold :: ([a] -> a) -> [a] unfold f = unfold1 f []
unfold1 :: ([a] -> a) -> [a] -> [a] unfold1 f l = f l : unfold1 f (f l : l)
Now I'm attempting to do the same thing, except where f returns a monad. (My use case is when f randomly selects the next element, i.e. text generation from markov chains.) So I want
unfoldM1 :: (Monad m) => ([a] -> m a) -> [a] -> m [a]
My instinct, then, would be to do something like:
unfoldM1 f l = do next <- f l rest <- unfoldM1 f (next : l) return (next : rest)
But that, like iRecurse above, doesn't work.
You could use a different type:
type IOStream a = (a, IO (IOStream a))
unfold :: ([a] -> IO a) -> IO (IOStream a) unfold f = let go prev = do next <- f prev return (next, go (next:prev)) in do z <- f [] go [z]
toList :: Int -> IOStream a -> IO [a] toList 0 _ = return [] toList n (x,rest) = do xs <- toList (n-1) rest return (x:xs)
Antoine

On Tue, May 31, 2011 at 6:10 PM, Antoine Latter
You could use a different type:
type IOStream a = (a, IO (IOStream a))
unfold :: ([a] -> IO a) -> IO (IOStream a) unfold f = let go prev = do next <- f prev return (next, go (next:prev)) in do z <- f [] go [z]
toList :: Int -> IOStream a -> IO [a] toList 0 _ = return [] toList n (x,rest) = do xs <- toList (n-1) rest return (x:xs)
Let's pretend I did that right:
toList :: Int -> IOStream a -> IO [a] toList 0 _ = return [] toList 1 (x,_) = return [x] toList n (x,r) = do rest <- r xs <- toList (n-1) rest return (x:xs)
Antoine

On a tangent, not doing IO, but food for thought: {-# LANGUAGE FlexibleContexts #-} import Control.Monad.State.Lazy as N import Control.Monad.State.Strict as S gen :: (MonadState [()] m) => m () gen = do gen modify (() :) many = take 3 (N.execState gen []) none = take 3 (S.execState gen [])
participants (9)
-
Albert Y. C. Lai
-
Anthony Cowley
-
Antoine Latter
-
Artyom Kazak
-
Daniel Fischer
-
Gregory Crosswhite
-
Scott Lawrence
-
Stephen Tetley
-
Yves Parès