Hi Paolino.

What's happening is reading [Char] uses the Storable instance for Char which is 32-bit. Thus, you get gibberish. The below does what you want, by reading Word8s and converting them.

import Control.Exception
import Data.Char
import Data.Iteratee.IO
import Data.Iteratee.Base
import Data.Word
import System.IO

main :: IO ()
main = do
       h <- openFile "mamma23" ReadWriteMode
       hPutStr h "ciao"
       hSeek h AbsoluteSeek 0
       l <- enumHandle h readString >>= run
       print $ assert (l == "ciao") ()

-- This is declared on its own so I can give a type signature without making
-- any of the above lines unmanageably long.
readString :: IterateeG [] Word8 IO String
readString = joinI $ mapStream (chr . fromIntegral) stream2list

This only works for ASCII, of course. Someone should write some enumerators for the other encodings.

Regards,
Echo Nolan
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to