Ronald J. Legere wrote:

 | getContents :: Handle -> IO String
 | getContents h = 
 |      do x <- hGetChar h
 |         xs <- getContents h
 |         return (x:xs)
 :
 | Well, I mean this would work, but it would not do it
 | lazily. How can I make it do it lazily?

As you found out, you can use the function
"unsafeInterleaveIO", provided by many Haskell compilers (at
least Hugs, GHC and HBC), but *not* part of the Haskell
standard.

This is because it is an *unsafe* function, a function that
might give strange results, a functione which is not
semantically well-defined. But somehow, unsafeInterleaveIO
is considered less harmful than the notorious
"unsafePerformIO".

The idea is as follows. Given any IO action "action",

  action :: IO result

"unsafeInterleaveIO action" is an IO action of the same
type, but, once executed, immediately terminates without
any side effects, returning something of type "result". Only
as soon as we evaluate this result, the side effects of the
IO action "action" will take place.

If we take the naive but popular standpoint of representing
the IO monad as a state monad:

  type IO a = World -> (a, World)

where the type "World" represents the state of the world,
then "unsafeInterleaveIO" can be seen as copying the world,
and leaving another world thread "dangling":

  unsafeInterleaveIO :: IO a -> IO a
  unsafeInterleaveIO f =
    \world1 ->
      let (a, world2) = f world1   -- using world1 twice
       in (a, world1)              -- where did world2 go?

As you can see, this works rather strangely. (I think this
is how it was implemented some time ago in an old version of
Hugs, when I learned what it did :-).

Some other Hugs implementation implemented
unsafeInterleaveIO as follows:

  unsafeInterleaveIO :: IO a -> IO a
  unsafeInterleaveIO =
    return . unsafePerformIO

But I am not sure if this is the correct behavior...

Finally, the implementation of "getContents" could be as
follows:

  getContents :: Handle -> IO String
  getContents h =
    unsafeInterleaveIO $ 
      do x  <- hGetChar h
         xs <- getContents h
         return (x:xs)

Note that we have to use "unsafeInterleaveIO" at every
element of the list (at every recursive call).

Hope this helps,
Koen.

--
Koen Claessen         http://www.cs.chalmers.se/~koen     
phone:+46-31-772 5424      e-mail:[EMAIL PROTECTED]
-----------------------------------------------------
Chalmers University of Technology, Gothenburg, Sweden


Reply via email to