[Haskell-cafe] Data.Binary and serialising doubles in IEEE format

Adam Langley agl at imperialviolet.org
Wed Jan 9 20:23:02 EST 2008


On Jan 9, 2008 5:18 AM, allan <a.d.clark at ed.ac.uk> wrote:
> Essentially then, is there anyone that can write my 'putDouble' function
> or give some hint as to how I might do it.
> For the moment assume that I'm not really concerned with portability
> across platforms at least for the time being (I certainly don't think
> that the C program I'm attempting to communicate with is particularly
> portable anyway).
>

I happen to have the reverse functions lying around which might be
some help in doing this. They aren't terribly beautiful, but they'll
take an IEEE double or float from a Bytestring and return the value +
the remaining ByteString. (They aren't very well tested, but they have
been found to mostly work).

ddouble :: BS.ByteString -> (Double, BS.ByteString)
ddouble bytes = (encodeFloat fraction $ fromIntegral exp, rest) where
  fraction = sign * fromIntegral ((n .&. 0xfffffffffffff) .|. (if
rawExp > 0 then 0x10000000000000 else 0))
  sign = if n `shiftR` 63 == 0 then 1 else -1
  exp = rawExp - (1023 + 52)
  rawExp = (n `shiftR` 52) .&. 0x7ff
  (b, rest) = BS.splitAt 8 bytes
  n :: Word64
  n = foldl1 (.|.) $ map (\(s, v) -> (fromIntegral v) `shiftL` s) $
zip [0,8..56] $ BS.unpack b

dfloat :: BS.ByteString -> (Float, BS.ByteString)
dfloat bytes = (encodeFloat fraction $ fromIntegral exp, rest) where
  fraction = sign * fromIntegral ((n .&. 0x7fffff) .|. (if rawExp > 0
then 0x800000 else 0))
  sign = if n `shiftR` 31 == 0 then 1 else -1
  exp = rawExp - (127 + 23)
  rawExp = (n `shiftR` 23) .&. 0xff
  (b, rest) = BS.splitAt 4 bytes
  n :: Word32
  n = foldl1 (.|.) $ map (\(s, v) -> (fromIntegral v) `shiftL` s) $
zip [0, 8, 16, 24] $ BS.unpack b


AGL

-- 
Adam Langley                                      agl at imperialviolet.org
http://www.imperialviolet.org                       650-283-9641


More information about the Haskell-Cafe mailing list