Writing binary files

Hi, 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. Thanks Neil

ndmitchell:
Hi,
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.
use the Binary class (or one of its cousins) darcs get http://www.n-heptane.com/nhlab/repos/NewBinary -- Don

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. -- Worrying is like rocking in a rocking chair -- It gives you something to do, but it doesn't get you anywhere.

Hi
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.)
It's exactly the answer I was hoping for! Thanks Neil

On 21/08/06, Udo Stenzel
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

Hello Alistair, Tuesday, August 22, 2006, 1:29:22 PM, you wrote:
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?
data written by your module on big-endian machine, can't be read by the same module in the little-end machine
bytes <- hGetBuf h p (sizeOf int32)
or bytes <- hGetBuf h p (sizeOf (0::Int32)) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (5)
-
Alistair Bayley
-
Bulat Ziganshin
-
dons@cse.unsw.edu.au
-
Neil Mitchell
-
Udo Stenzel