[Haskell-cafe] Writing binary files?

Jan-Willem Maessen - Sun Labs East Janwillem.Maessen at Sun.COM
Mon Sep 13 10:51:18 EDT 2004


Abraham Egnor wrote:
> Passing a Ptr isn't that onerous; it's easy enough to make functions
> that have the signature you'd like:
> 
> import System.IO
> import Data.Word (Word8)
> import Foreign.Marshal.Array
> 
> hPutBytes :: Handle -> [Word8] -> IO ()
> hPutBytes h ws = withArray ws $ \p -> hPutBuf h p $ length ws
> 
> hGetBytes :: Handle -> Int -> IO [Word8]
> hGetBytes h c = allocaArray c $ \p ->
>     do c' <- hGetBuf h p c
>        peekArray c' p

If it's that simple, why don't the libraries provide it?  It would 
save a lot of traffic on haskell and haskell-cafe alone. :-)

-Jan-Willem Maessen

> 
> 
> On Sun, 12 Sep 2004 14:24:56 +0100, Glynn Clements
> <glynn.clements at virgin.net> wrote:
> 
>>Sven Panne wrote:
>>
>>
>>>>[...]
>>>>    main :: IO ()
>>>>    main = do
>>>>            h <- openBinaryFile "out.dat" WriteMode
>>>>            hPutStr h $ map (octetToChar . bitsToOctet) bits
>>>>            hClose h
>>>
>>>Hmmm, using string I/O when one really wants to do binary I/O gives me a bad
>>>feeling. Haskell characters are defined to be Unicode characters, so the
>>>above only works because current Haskell implementations usually get this wrong
>>>(either no Unicode support at all and/or ignoring any encodings and doing I/O
>>>only with the lower 8 bits of the characters)... hGetBuf/hPutBuf plus their
>>>non-blocking variants are the only way to *really* do binary I/O currently.
>>
>>Which is unfortunate, because of the requirement to pass a Ptr. We
>>really need "hPutBytes :: [Word8] -> IO ()" etc.
>>
>>Also, changing the existing functions to deal with encodings is likely
>>to break a lot of things (i.e. anything which reads or writes data
>>which is in neither UTF-8 nor the locale-specified encoding).
>>
>>
>>
>>--
>>Glynn Clements <glynn.clements at virgin.net>
>>_______________________________________________
>>Haskell-Cafe mailing list
>>Haskell-Cafe at haskell.org
>>http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list