Bug in hGetBufBA + hIsEOF

2001-12-10 Thread Koen Claessen

Hi,

Given a file test of size 2342.

The program Bug.hs behaves correctly (the result is
(2048,384)), but when uncommenting the seemingly innocent
line, the program behaves incorrectly (result is
(2048,2048)), and the buffer is filled with garbage.

main =
  do han - openFile test ReadMode
 arr - stToIO (newCharArray (0,2048))
 n1  - hGetBufBA han arr 2048
 --eof - hIsEOF han
 n2  - hGetBufBA han arr 2048
 print (n1,n2)

I am using solaris and GHC 5.02.1.

Thanks,
/Koen.


module DataStream where

import IO
import IOExts
import MutableArray
import ST
import GlaExts

main =
  do dat - readFileData DataStream.hs
 writeFileData copy.hs dat


-- Data

newtype Data = MkData [(Int,MutableByteArray RealWorld Int)]


-- reading, writing

hGetData :: Handle - IO Data
hGetData han =
  do xs - get
 return (MkData xs)
 where
  get =
unsafeInterleaveIO (
  do arr - stToIO (newCharArray (0,blockSize))
 putStrLn Reading ...
 n   - hGetBufBA han arr blockSize
 putStrLn ((read  ++ show n ++  bytes))
 --eof - hIsEOF han
 let eof = n /= blockSize
 xs  - if eof then return [] else do hIsEOF han; get
 return ((n,arr):xs)
)

hPutData :: Handle - Data - IO ()
hPutData han (MkData xs) =
  sequence_ [ do hPutBufBA han arr n
 putStrLn ((written  ++ show n ++  bytes))
| (n,arr) - xs ]

blockSize :: Int
blockSize = 2048


-- files

readFileData :: FilePath - IO Data
readFileData file =
  do han - openFile file ReadMode
 hGetData han

writeFileData :: FilePath - Data - IO ()
writeFileData file dat =
  do han - openFile file WriteMode
 hPutData han dat
 hClose han

appendFileData :: FilePath - Data - IO ()
appendFileData file dat =
  do han - openFile file AppendMode
 hPutData han dat
 hClose han

{-

-- operations

toData :: String - Data
toData s =
  unsafePerformST (
do arr - newCharArray (0,n)
   sequence_ [ writeCharArray arr i c | (i,c) - [0..] `zip` s ]
   return (MkData [(n,arr)])
  )
 where
  n = length s - 1

fromData :: Data - String
fromData (MkData xs) =
  concat (unsafePerformST (sequence [ read n arr | (n,arr) - xs ]))
 where
  read n arr =
sequence [ readCharArray arr i | i - [0..n] ]

(+++) :: Data - Data - Data
MkData xs +++ MkData ys = MkData (xs ++ ys)


-- helpers

unsafePerformST :: ST RealWorld a - a
unsafePerformST m = unsafePerformIO (stToIO m)
-}

-- the end.



module Main where

import IO
import IOExts
import MutableArray
import ST
import GlaExts

main =
  do han - openFile test ReadMode
 arr - stToIO (newCharArray (0,2048))
 n1  - hGetBufBA han arr 2048
 --eof - hIsEOF han
 n2  - hGetBufBA han arr 2048
 print (n1,n2)


 
 





RE: Bug in hGetBufBA + hIsEOF

2001-12-10 Thread Simon Marlow


 Given a file test of size 2342.
 
 The program Bug.hs behaves correctly (the result is
 (2048,384)), but when uncommenting the seemingly innocent
 line, the program behaves incorrectly (result is
 (2048,2048)), and the buffer is filled with garbage.
 
 main =
   do han - openFile test ReadMode
  arr - stToIO (newCharArray (0,2048))
  n1  - hGetBufBA han arr 2048
  --eof - hIsEOF han
  n2  - hGetBufBA han arr 2048
  print (n1,n2)
 
 I am using solaris and GHC 5.02.1.

Thanks, that's a bug.  Workaround: hGetBufBA will only return a value
less than the specified count if EOF is reached, so you can detect EOF
that way.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs