[Haskell-cafe] Writing binary files

Alistair Bayley alistair at abayley.org
Tue Aug 22 05:29:22 EDT 2006


On 21/08/06, Udo Stenzel <u.stenzel at web.de> wrote:
> Neil Mitchell wrote:
> > I'm trying to write out a binary file, in particular I want the
> > following functions:
> >
> > hPutInt :: Handle -> Int -> IO ()
> >
> > hGetInt :: Handle -> IO Int
> >
> > For the purposes of these functions, Int = 32 bits, and its got to
> > roundtrip - Put then Get must be the same.
> >
> > How would I do this? I see Ptr, Storable and other things, but nothing
> > which seems directly useable for me.
>
>
> hPutInt h = hPutStr h . map chr . map (0xff .&.)
>                       . take 4 . iterate (`shiftR` 8)
>
> hGetInt h = replicateM 4 (hGetChar h) >>=
>             return . foldr (\i d -> i `shiftL` 8 .|. ord d) 0
>
> This of course assumes that a Char is read/written as a single low-order
> byte without any conversion.  But you'd have to assume a lot more if you
> started messing with pointers.  (Strange, somehow I get the feeling, the
> above is way too easy to be the answer you wanted.)
>
>
> Udo.

What's wrong with the following i.e. what assumptions is it making
(w.r.t. pointers) that I've missed? Is endian-ness an issue here?

Alistair


hPutInt :: Handle -> Int32 -> IO ()
hGetInt :: Handle -> IO Int32

int32 :: Int32
int32 = 0

hPutInt h i = do
  alloca $ \p -> do
  poke p i
  hPutBuf h p (sizeOf i)

hGetInt h = do
  alloca $ \p -> do
  bytes <- hGetBuf h p (sizeOf int32)
  when (bytes < sizeOf int32) (error "too few bytes read")
  peek p


More information about the Haskell-Cafe mailing list