Wed Oct 8 20:03:00 EDT 2008 Peter Gavin <pg...@gm...>
* update tools/c2hs/base/general/Binary.hs to work with GHC 6.10
the instance for Binary Integer needed to be rewritten, because the old version used internal data for the Integer type.
The new instance only uses Bits functions, so should be portable.
hunk ./tools/c2hs/base/general/Binary.hs 41
+#if __GLASGOW_HASKELL__<610
hunk ./tools/c2hs/base/general/Binary.hs 46
+#endif
hunk ./tools/c2hs/base/general/Binary.hs 75
+# if __GLASGOW_HASKELL__<610
hunk ./tools/c2hs/base/general/Binary.hs 77
+# else
+import Control.OldException ( throwDyn )
+# endif
hunk ./tools/c2hs/base/general/Binary.hs 483
+#if __GLASGOW_HASKELL__<610
hunk ./tools/c2hs/base/general/Binary.hs 559
+
+#else
+
+instance Binary Integer where
+ put_ h n = do
+ put h ((fromIntegral $ signum n) :: Int8)
+ when (n /= 0) $ do
+ let n' = abs n
+ nBytes = byteSize n'
+ put h (fromIntegral nBytes :: Word64)
+ mapM_ (putByte h) [ fromIntegral ((n' `shiftR` (b * 8)) .&. 0xff)
+ | b <- [ nBytes-1, nBytes-2 .. 0 ] ]
+ where byteSize n =
+ let f b = if (1 `shiftL` (b * 8)) > n
+ then b
+ else f (b + 1)
+ in f 0
+ get h = do
+ sign :: Int8 <- get h
+ if sign == 0
+ then return 0
+ else do
+ nBytes :: Word64 <- get h
+ n <- accumBytes nBytes 0
+ return $ fromIntegral sign * n
+ where accumBytes nBytes acc | nBytes == 0 = return acc
+ | otherwise = do
+ b <- getByte h
+ accumBytes (nBytes - 1) ((acc `shiftL` 8) .|. fromIntegral b)
+#endif
+
|