[Haskell-cafe] ... - what about introducing LazyIO ?

Marc Weber marco-oweber at gmx.de
Tue Apr 17 19:24:07 EDT 2007


> sequence isn't lazy (not in the IO monad at least); it will try to run
> to completion, returning an infinite list of (as yet unevaluated, due

I should have learned that lesson already..

This is the second time I could have needed a lazy IO monad version..
Does something like this already exist?

============= LazyIO test ============================================
module Main where
import Control.Monad
import System.IO.Unsafe

import Random

data LazyIO a = LazyIO (IO a)

-- conversion 
unLazy :: LazyIO a -> IO a
unLazy (LazyIO a) = a

-- my lazy monad
instance Monad LazyIO where
  return a = LazyIO (return a)
  (LazyIO m) >>= k = LazyIO $ unsafeInterleaveIO $ m >>= unLazy . k

main = do
  print "LazyIO test"
  putStrLn "this should work : (LazyIO version)"
  randoms <-  unLazy . sequence . cycle $ [ LazyIO (randomIO :: IO Int) ]
  print $ take 5 randoms
  putStrLn "this should hang : (IO version)"
  randoms <-  sequence . cycle $ [ randomIO :: IO Int ]
  print $ take 5 randoms
============= LazyIO test ============================================

compare this (adding unLazy and LazyIO) to reimplementing 
sequence, mapM, ...
> > unsafeInterleaveSequence :: [IO a] -> IO [a]
> > unsafeInterleaveSequence []     = return []
> > unsafeInterleaveSequence (x:xs) =
> >      unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs)

I really start to love haskell :)
Marc


More information about the Haskell-Cafe mailing list