Problems with 'readFile'

Alexandre Weffort Thenorio alethenorio@home.se
Fri, 23 May 2003 22:59:07 +0200


Hi. Well I have no idea which is the ASCII character 26 but remember that it
will stop if it encounters a EOF character (Although that doesn't seem to be
the case). Why don't you try Openfile to see if it gives same error??

Something like:

main = do let output = problemtext
      putStr output
      putStr "\n\n"
      writeFile "outputfile.txt" output
          text <- openFile "outputfile.txt" ReadMode
          y <- hGetContents text

      PutStr y


If problem persists you could use the IOExts Library (I believe that it is
only found in ghc) and read it in binary mode.
Something like:

Import IOExts

main = do let output = problemtext
      putStr output
      putStr "\n\n"
      writeFile "outputfile.txt" output
          text <- openFileEx "outputfile.txt" (BinaryMode ReadMode)
          y <- hGetContents text

      PutStr y

Remember to use lang package in case you compile it. Let us know how you get
on.

Best Regards

NooK


----- Original Message ----- 
From: "Niels Reyngoud" <nreijngo@cs.uu.nl>
To: <haskell@haskell.org>
Sent: Friday, May 23, 2003 10:07 AM
Subject: Problems with 'readFile'


> Hello,
>
> We are two students from the University of Utrecht (the Netherlands)
> working on a project in Haskell. During work on the project, we
> encountered a problem with the 'readFile' IO Monad.  readFile stops
> reading a file when it encounters ASCII character 26, as the following
> piece of coding shows. We've tested this with both the Hugs interpreter
> and the GHC compiler, but both encounter the same problem. Are there any
> known solutions for this?
>
> Regards,
> Richard Nieuwenhuis and Niels Reyngoud
>
>
> ------------
>
> module Main where
>
> main = do let output = problemtext
>       putStr output
>       putStr "\n\n"
>       writeFile "outputfile.txt" output
>           text <- readFile "outputfile.txt"
>       putStr text
>
>
> problemtext :: String
> problemtext = "strange\SUBstrange"
>
>
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>