Suppose the code
f :: IO [Int]
f = f >>= return . (0 :)
g :: IO [Int]
g = f >>= return . take 3
When I run g
in ghci, it cause stackoverflow. But I was thinking maybe it could be evaluated lazily and produce [0, 0, 0]
wrapped in IO
. I suspect IO
is to blame here, but I really have no idea. Obviously the following works:
f' :: [Int]
f' = 0 : f'
g' :: [Int]
g' = take 3 f'
Edit: In fact I am not interested in having such a simple function f
, original code looked more along the lines:
h :: a -> IO [Either b c]
h a = do
(r, a') <- h' a
case r of
x@(Left _) -> h a' >>= return . (x :)
y@(Right _) -> return [y]
h' :: IO (Either b c, a)
-- something non trivial
main :: IO ()
main = mapM_ print . take 3 =<< h a
h
does some IO
computations and stores invalid (Left
) responses in a list until a valid response (Right
) is produced. The attempt is to construct the list lazily even though we are in the IO
monad. So that someone reading the result of h
can start consuming the list even before it is complete (because it may even be infinite). And if the one reading the results cares only for the first 3
entries no matter what, the rest of the list does not even have to be constructed. And I am getting the feeling that this will not be possible :/.
I'm not sure if this is an appropriate usage, but unsafeInterleaveIO
would get you the behavior you're asking for, by deferring the IO actions of f
until the value inside of f
is asked for:
module Tmp where
import System.IO.Unsafe (unsafeInterleaveIO)
f :: IO [Int]
f = unsafeInterleaveIO f >>= return . (0 :)
g :: IO [Int]
g = f >>= return . take 3
*Tmp> g
[0,0,0]