[Haskell-cafe] Error in enumerator when using interpreter instead of compiler

Tobias Brandt tob.brandt at googlemail.com
Sun Aug 22 17:46:10 EDT 2010


Hi all,
I was trying out the enumerator package. I wanted to copy the contents of
one file to another:

module Main where
import Data.Enumerator
import Data.Enumerator.IO

main = run (enumFile "foo" $$ iterFile "bar")

If I compile this code with GHC, it works as expected. But if I run it with
runhaskell I get the following error:
Left bar: hPutBuf: illegal operation (handle is closed)

If I replace the above code with this:

module Main where
import Data.Enumerator
import Data.Enumerator.IO
import System.IO

main = withBinaryFile "bar" WriteMode $ \h ->
    run (enumFile "foo" $$ iterHandle h)

It works both compiled and interpreted.

Is this a bug in enumerator (probably in the iterFile function) or a
deficiency of the interpreter?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100822/b56252d2/attachment.html


More information about the Haskell-Cafe mailing list