[Haskell-cafe] Writing binary files?
Glynn Clements
glynn.clements at virgin.net
Sat Sep 11 18:12:21 EDT 2004
Ron de Bruijn wrote:
> Basically, I just want to have a function, that
> converts a list with zeros and ones to a binary file
> and the other way around.
>
> If I write 11111111 to a file, it would take 8 bytes.
> But I want it to take 8 bits.
import Char (digitToInt, chr)
import Word (Word8)
import System.IO (openBinaryFile)
import IO (IOMode(..), hPutStr, hClose)
bitsToOctet :: [Char] -> Word8
bitsToOctet ds = fromIntegral $ sum $ zipWith (*) powers digits
where powers = [2^n | n <- [7,6..0]]
digits = map digitToInt ds
octetToChar :: Word8 -> Char
octetToChar = chr . fromIntegral
bits :: [[Char]]
bits = [ "01101000" -- 0x68 'h'
, "01100101" -- 0x65 'e'
, "01101100" -- 0x6c 'l'
, "01101100" -- 0x6c 'l'
, "01101111" -- 0x6f 'o'
, "00001010" -- 0x0a '\n'
]
main :: IO ()
main = do
h <- openBinaryFile "out.dat" WriteMode
hPutStr h $ map (octetToChar . bitsToOctet) bits
hClose h
--
Glynn Clements <glynn.clements at virgin.net>
More information about the Haskell-Cafe
mailing list