Binary files and NHC98

José Romildo Malaquias romildo@urano.iceb.ufop.br
Sat, 14 Oct 2000 03:48:06 -0200


--wRRV7LY7NUeQGEoC
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

In order to experiment with the Binary module
distributed with nhc98, I wrote the attached
program which writes a binary file and then
reads it. When executed, I got an extra
byte (8) that I cannot explain:

	[65,66,67,68,8]

Any clues why it appears?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--wRRV7LY7NUeQGEoC
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="BinaryFile.hs"

module Main where

import IO (IOMode(ReadMode,WriteMode))
import Binary (openBin,closeBin,getBits,putBits,isEOFBin,
               BinIOMode(RO,WO),BinLocation(File),BinHandle)

-- convert from IOMode to BinIOMode
ioModeToBinIOMode           :: IOMode -> BinIOMode
ioModeToBinIOMode ReadMode   = RO
ioModeToBinIOMode WriteMode  = WO

-- open a binary file
openBinaryFile          :: FilePath -> IOMode -> IO BinHandle
openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode))

-- write a list of integers (8 bits) to binary file
writeBinaryFile   	:: FilePath -> [Int] -> IO ()
writeBinaryFile fileName xs =
    do f <- openBinaryFile fileName WriteMode
       let writeToBin [] = return ()
           writeToBin (x:xs) = do putBits f 8 x
                                  writeToBin xs
       writeToBin xs
       closeBin f

-- read a list of integers (8 bits) from binary file
readBinaryFile  :: FilePath -> IO [Int]
readBinaryFile fileName =
    do f <- openBinaryFile fileName ReadMode
       let readFromBin = do eof <- isEOFBin f
                            if eof
                               then return []
                               else do x <- getBits f 8
                                       xs <- readFromBin
                                       return (x:xs)
       xs <- readFromBin
       closeBin f
       return xs

-- test the above
main = do writeBinaryFile "test.bin" [65,66,67,68]
          xs <- readBinaryFile "test.bin"
          putStrLn (show xs)

--wRRV7LY7NUeQGEoC--