Johannes Waldmann wrote:
> i'd like to read a byte stream from stdin. the stream contains 0xFF
> now and then. i fear that such a byte is treated as EOF by ghc,
> because processing seems to stop right after it first occured.

Hmmm, I've never experienced something like this. The following code
snippet from my Quake level viewer works fine:

-------------------------------------------------------------------
...
qGetN :: Integral a => a -> (Handle -> IO b) -> Handle -> IO [b]
qGetN n f = sequence . replicate (fromIntegral n) . f

-- read n bytes, Intel-like
readBytes :: Num a => Int -> Handle -> IO a
readBytes n h =
   liftM (foldr (\x val -> val * 256 + fromIntegral (fromEnum x)) 0)
         (qGetN n hGetChar h)
...
type Qushort = Word16

qushortSize :: Int
qushortSize = 2

qGetQushort :: Handle -> IO Qushort
qGetQushort = readBytes qushortSize
...
-------------------------------------------------------------------

What GHC version/platform are you using?

But Haskell *really* needs some standard way of reading values in the
native format on a platform:

   http://www.informatik.uni-muenchen.de/haskell-wish-list/items.php3?id=5

Why? Just have a look at the following stuff:    :-P

-------------------------------------------------------------------
type Qfloat = Float -- hopefully 32-bit IEEE floating point

qfloatSize :: Int
qfloatSize = 4

-- Aaaaaargl!!!!!!!
qGetQfloat :: Handle -> IO Qfloat
qGetQfloat h = do
   a <- hGetChar h
   b <- hGetChar h
   c <- hGetChar h
   d <- hGetChar h
   _casm_ ``union {float f; char c[4];} x; x.c[0]=%0; x.c[1]=%1; x.c[2]=%2; x.c[3]=%3; 
%r=x.f;'' a b c d
-------------------------------------------------------------------

Embarrassing...

Cheers,
   Sven
-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne

Reply via email to