module Binary
( Bin,
Binary(..),
BinHandle,
openBinIO, openBinIO_,
openBinMem,
seekBin,
seekBy,
tellBin,
castBin,
writeBinMem,
readBinMem,
fingerprintBinMem,
isEOFBin,
putAt, getAt,
putByte,
getByte,
lazyGet,
lazyPut,
#ifdef __GLASGOW_HASKELL__
ByteArray(..),
getByteArray,
putByteArray,
#endif
UserData(..), getUserData, setUserData,
newReadState, newWriteState,
putDictionary, getDictionary, putFS,
) where
#include "HsVersions.h"
#include "../includes/MachDeps.h"
import Name (Name)
import FastString
import Panic
import UniqFM
import FastMutInt
import Fingerprint
import BasicTypes
import Foreign
import Data.Array
import Data.IORef
import Data.Char ( ord, chr )
import Data.Typeable
import Control.Monad ( when )
import System.IO as IO
import System.IO.Unsafe ( unsafeInterleaveIO )
import System.IO.Error ( mkIOError, eofErrorType )
import GHC.Real ( Ratio(..) )
import GHC.Exts
import GHC.Word ( Word8(..) )
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO ( IO(..) )
#else
import GHC.IOBase ( IO(..) )
#endif
type BinArray = ForeignPtr Word8
data BinHandle
= BinMem {
bh_usr :: UserData,
_off_r :: !FastMutInt,
_sz_r :: !FastMutInt,
_arr_r :: !(IORef BinArray)
}
| BinIO {
bh_usr :: UserData,
_off_r :: !FastMutInt,
_hdl :: !IO.Handle
}
getUserData :: BinHandle -> UserData
getUserData bh = bh_usr bh
setUserData :: BinHandle -> UserData -> BinHandle
setUserData bh us = bh { bh_usr = us }
newtype Bin a = BinPtr Int
deriving (Eq, Ord, Show, Bounded)
castBin :: Bin a -> Bin b
castBin (BinPtr i) = BinPtr i
class Binary a where
put_ :: BinHandle -> a -> IO ()
put :: BinHandle -> a -> IO (Bin a)
get :: BinHandle -> IO a
put_ bh a = do _ <- put bh a; return ()
put bh a = do p <- tellBin bh; put_ bh a; return p
putAt :: Binary a => BinHandle -> Bin a -> a -> IO ()
putAt bh p x = do seekBin bh p; put_ bh x; return ()
getAt :: Binary a => BinHandle -> Bin a -> IO a
getAt bh p = do seekBin bh p; get bh
openBinIO_ :: IO.Handle -> IO BinHandle
openBinIO_ h = openBinIO h
openBinIO :: IO.Handle -> IO BinHandle
openBinIO h = do
r <- newFastMutInt
writeFastMutInt r 0
return (BinIO noUserData r h)
openBinMem :: Int -> IO BinHandle
openBinMem size
| size <= 0 = error "Data.Binary.openBinMem: size must be >= 0"
| otherwise = do
arr <- mallocForeignPtrBytes size
arr_r <- newIORef arr
ix_r <- newFastMutInt
writeFastMutInt ix_r 0
sz_r <- newFastMutInt
writeFastMutInt sz_r size
return (BinMem noUserData ix_r sz_r arr_r)
tellBin :: BinHandle -> IO (Bin a)
tellBin (BinIO _ r _) = do ix <- readFastMutInt r; return (BinPtr ix)
tellBin (BinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix)
seekBin :: BinHandle -> Bin a -> IO ()
seekBin (BinIO _ ix_r h) (BinPtr p) = do
writeFastMutInt ix_r p
hSeek h AbsoluteSeek (fromIntegral p)
seekBin h@(BinMem _ ix_r sz_r _) (BinPtr p) = do
sz <- readFastMutInt sz_r
if (p >= sz)
then do expandBin h p; writeFastMutInt ix_r p
else writeFastMutInt ix_r p
seekBy :: BinHandle -> Int -> IO ()
seekBy (BinIO _ ix_r h) off = do
ix <- readFastMutInt ix_r
let ix' = ix + off
writeFastMutInt ix_r ix'
hSeek h AbsoluteSeek (fromIntegral ix')
seekBy h@(BinMem _ ix_r sz_r _) off = do
sz <- readFastMutInt sz_r
ix <- readFastMutInt ix_r
let ix' = ix + off
if (ix' >= sz)
then do expandBin h ix'; writeFastMutInt ix_r ix'
else writeFastMutInt ix_r ix'
isEOFBin :: BinHandle -> IO Bool
isEOFBin (BinMem _ ix_r sz_r _) = do
ix <- readFastMutInt ix_r
sz <- readFastMutInt sz_r
return (ix >= sz)
isEOFBin (BinIO _ _ h) = hIsEOF h
writeBinMem :: BinHandle -> FilePath -> IO ()
writeBinMem (BinIO _ _ _) _ = error "Data.Binary.writeBinMem: not a memory handle"
writeBinMem (BinMem _ ix_r _ arr_r) fn = do
h <- openBinaryFile fn WriteMode
arr <- readIORef arr_r
ix <- readFastMutInt ix_r
withForeignPtr arr $ \p -> hPutBuf h p ix
hClose h
readBinMem :: FilePath -> IO BinHandle
readBinMem filename = do
h <- openBinaryFile filename ReadMode
filesize' <- hFileSize h
let filesize = fromIntegral filesize'
arr <- mallocForeignPtrBytes (filesize*2)
count <- withForeignPtr arr $ \p -> hGetBuf h p filesize
when (count /= filesize) $
error ("Binary.readBinMem: only read " ++ show count ++ " bytes")
hClose h
arr_r <- newIORef arr
ix_r <- newFastMutInt
writeFastMutInt ix_r 0
sz_r <- newFastMutInt
writeFastMutInt sz_r filesize
return (BinMem noUserData ix_r sz_r arr_r)
fingerprintBinMem :: BinHandle -> IO Fingerprint
fingerprintBinMem (BinIO _ _ _) = error "Binary.md5BinMem: not a memory handle"
fingerprintBinMem (BinMem _ ix_r _ arr_r) = do
arr <- readIORef arr_r
ix <- readFastMutInt ix_r
withForeignPtr arr $ \p -> fingerprintData p ix
expandBin :: BinHandle -> Int -> IO ()
expandBin (BinMem _ _ sz_r arr_r) off = do
sz <- readFastMutInt sz_r
let sz' = head (dropWhile (<= off) (iterate (* 2) sz))
arr <- readIORef arr_r
arr' <- mallocForeignPtrBytes sz'
withForeignPtr arr $ \old ->
withForeignPtr arr' $ \new ->
copyBytes new old sz
writeFastMutInt sz_r sz'
writeIORef arr_r arr'
when False $
hPutStrLn stderr ("Binary: expanding to size: " ++ show sz')
return ()
expandBin (BinIO _ _ _) _ = return ()
putWord8 :: BinHandle -> Word8 -> IO ()
putWord8 h@(BinMem _ ix_r sz_r arr_r) w = do
ix <- readFastMutInt ix_r
sz <- readFastMutInt sz_r
if (ix >= sz)
then do expandBin h ix
putWord8 h w
else do arr <- readIORef arr_r
withForeignPtr arr $ \p -> pokeByteOff p ix w
writeFastMutInt ix_r (ix+1)
return ()
putWord8 (BinIO _ ix_r h) w = do
ix <- readFastMutInt ix_r
hPutChar h (chr (fromIntegral w))
writeFastMutInt ix_r (ix+1)
return ()
getWord8 :: BinHandle -> IO Word8
getWord8 (BinMem _ ix_r sz_r arr_r) = do
ix <- readFastMutInt ix_r
sz <- readFastMutInt sz_r
when (ix >= sz) $
ioError (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
arr <- readIORef arr_r
w <- withForeignPtr arr $ \p -> peekByteOff p ix
writeFastMutInt ix_r (ix+1)
return w
getWord8 (BinIO _ ix_r h) = do
ix <- readFastMutInt ix_r
c <- hGetChar h
writeFastMutInt ix_r (ix+1)
return $! (fromIntegral (ord c))
putByte :: BinHandle -> Word8 -> IO ()
putByte bh w = put_ bh w
getByte :: BinHandle -> IO Word8
getByte = getWord8
instance Binary Word8 where
put_ = putWord8
get = getWord8
instance Binary Word16 where
put_ h w = do
putByte h (fromIntegral (w `shiftR` 8))
putByte h (fromIntegral (w .&. 0xff))
get h = do
w1 <- getWord8 h
w2 <- getWord8 h
return $! ((fromIntegral w1 `shiftL` 8) .|. fromIntegral w2)
instance Binary Word32 where
put_ h w = do
putByte h (fromIntegral (w `shiftR` 24))
putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff))
putByte h (fromIntegral (w .&. 0xff))
get h = do
w1 <- getWord8 h
w2 <- getWord8 h
w3 <- getWord8 h
w4 <- getWord8 h
return $! ((fromIntegral w1 `shiftL` 24) .|.
(fromIntegral w2 `shiftL` 16) .|.
(fromIntegral w3 `shiftL` 8) .|.
(fromIntegral w4))
instance Binary Word64 where
put_ h w = do
putByte h (fromIntegral (w `shiftR` 56))
putByte h (fromIntegral ((w `shiftR` 48) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 40) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 32) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 24) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff))
putByte h (fromIntegral (w .&. 0xff))
get h = do
w1 <- getWord8 h
w2 <- getWord8 h
w3 <- getWord8 h
w4 <- getWord8 h
w5 <- getWord8 h
w6 <- getWord8 h
w7 <- getWord8 h
w8 <- getWord8 h
return $! ((fromIntegral w1 `shiftL` 56) .|.
(fromIntegral w2 `shiftL` 48) .|.
(fromIntegral w3 `shiftL` 40) .|.
(fromIntegral w4 `shiftL` 32) .|.
(fromIntegral w5 `shiftL` 24) .|.
(fromIntegral w6 `shiftL` 16) .|.
(fromIntegral w7 `shiftL` 8) .|.
(fromIntegral w8))
instance Binary Int8 where
put_ h w = put_ h (fromIntegral w :: Word8)
get h = do w <- get h; return $! (fromIntegral (w::Word8))
instance Binary Int16 where
put_ h w = put_ h (fromIntegral w :: Word16)
get h = do w <- get h; return $! (fromIntegral (w::Word16))
instance Binary Int32 where
put_ h w = put_ h (fromIntegral w :: Word32)
get h = do w <- get h; return $! (fromIntegral (w::Word32))
instance Binary Int64 where
put_ h w = put_ h (fromIntegral w :: Word64)
get h = do w <- get h; return $! (fromIntegral (w::Word64))
instance Binary () where
put_ _ () = return ()
get _ = return ()
instance Binary Bool where
put_ bh b = putByte bh (fromIntegral (fromEnum b))
get bh = do x <- getWord8 bh; return $! (toEnum (fromIntegral x))
instance Binary Char where
put_ bh c = put_ bh (fromIntegral (ord c) :: Word32)
get bh = do x <- get bh; return $! (chr (fromIntegral (x :: Word32)))
instance Binary Int where
put_ bh i = put_ bh (fromIntegral i :: Int64)
get bh = do
x <- get bh
return $! (fromIntegral (x :: Int64))
instance Binary a => Binary [a] where
put_ bh l = do
let len = length l
if (len < 0xff)
then putByte bh (fromIntegral len :: Word8)
else do putByte bh 0xff; put_ bh (fromIntegral len :: Word32)
mapM_ (put_ bh) l
get bh = do
b <- getByte bh
len <- if b == 0xff
then get bh
else return (fromIntegral b :: Word32)
let loop 0 = return []
loop n = do a <- get bh; as <- loop (n1); return (a:as)
loop len
instance (Binary a, Binary b) => Binary (a,b) where
put_ bh (a,b) = do put_ bh a; put_ bh b
get bh = do a <- get bh
b <- get bh
return (a,b)
instance (Binary a, Binary b, Binary c) => Binary (a,b,c) where
put_ bh (a,b,c) = do put_ bh a; put_ bh b; put_ bh c
get bh = do a <- get bh
b <- get bh
c <- get bh
return (a,b,c)
instance (Binary a, Binary b, Binary c, Binary d) => Binary (a,b,c,d) where
put_ bh (a,b,c,d) = do put_ bh a; put_ bh b; put_ bh c; put_ bh d
get bh = do a <- get bh
b <- get bh
c <- get bh
d <- get bh
return (a,b,c,d)
instance Binary a => Binary (Maybe a) where
put_ bh Nothing = putByte bh 0
put_ bh (Just a) = do putByte bh 1; put_ bh a
get bh = do h <- getWord8 bh
case h of
0 -> return Nothing
_ -> do x <- get bh; return (Just x)
instance (Binary a, Binary b) => Binary (Either a b) where
put_ bh (Left a) = do putByte bh 0; put_ bh a
put_ bh (Right b) = do putByte bh 1; put_ bh b
get bh = do h <- getWord8 bh
case h of
0 -> do a <- get bh ; return (Left a)
_ -> do b <- get bh ; return (Right b)
#if defined(__GLASGOW_HASKELL__) || 1
instance Binary Integer where
put_ bh i = put_ bh (show i)
get bh = do str <- get bh
case reads str of
[(i, "")] -> return i
_ -> fail ("Binary Integer: got " ++ show str)
putByteArray :: BinHandle -> ByteArray# -> Int# -> IO ()
putByteArray bh a s# = loop 0#
where loop n#
| n# ==# s# = return ()
| otherwise = do
putByte bh (indexByteArray a n#)
loop (n# +# 1#)
getByteArray :: BinHandle -> Int -> IO ByteArray
getByteArray bh (I# sz) = do
(MBA arr) <- newByteArray sz
let loop n
| n ==# sz = return ()
| otherwise = do
w <- getByte bh
writeByteArray arr n w
loop (n +# 1#)
loop 0#
freezeByteArray arr
data ByteArray = BA ByteArray#
data MBA = MBA (MutableByteArray# RealWorld)
newByteArray :: Int# -> IO MBA
newByteArray sz = IO $ \s ->
case newByteArray# sz s of { (# s, arr #) ->
(# s, MBA arr #) }
freezeByteArray :: MutableByteArray# RealWorld -> IO ByteArray
freezeByteArray arr = IO $ \s ->
case unsafeFreezeByteArray# arr s of { (# s, arr #) ->
(# s, BA arr #) }
writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO ()
writeByteArray arr i (W8# w) = IO $ \s ->
case writeWord8Array# arr i w s of { s ->
(# s, () #) }
indexByteArray :: ByteArray# -> Int# -> Word8
indexByteArray a# n# = W8# (indexWord8Array# a# n#)
instance (Integral a, Binary a) => Binary (Ratio a) where
put_ bh (a :% b) = do put_ bh a; put_ bh b
get bh = do a <- get bh; b <- get bh; return (a :% b)
#endif
instance Binary (Bin a) where
put_ bh (BinPtr i) = put_ bh (fromIntegral i :: Int32)
get bh = do i <- get bh; return (BinPtr (fromIntegral (i :: Int32)))
instance Binary TyCon where
put_ bh ty_con = do
let s = tyConString ty_con
put_ bh s
get bh = do
s <- get bh
return (mkTyCon s)
instance Binary TypeRep where
put_ bh type_rep = do
let (ty_con, child_type_reps) = splitTyConApp type_rep
put_ bh ty_con
put_ bh child_type_reps
get bh = do
ty_con <- get bh
child_type_reps <- get bh
return (mkTyConApp ty_con child_type_reps)
lazyPut :: Binary a => BinHandle -> a -> IO ()
lazyPut bh a = do
pre_a <- tellBin bh
put_ bh pre_a
put_ bh a
q <- tellBin bh
putAt bh pre_a q
seekBin bh q
lazyGet :: Binary a => BinHandle -> IO a
lazyGet bh = do
p <- get bh
p_a <- tellBin bh
a <- unsafeInterleaveIO (getAt bh p_a)
seekBin bh p
return a
data UserData =
UserData {
ud_dict :: Dictionary,
ud_symtab :: SymbolTable,
ud_put_name :: BinHandle -> Name -> IO (),
ud_put_fs :: BinHandle -> FastString -> IO ()
}
newReadState :: Dictionary -> IO UserData
newReadState dict = do
return UserData { ud_dict = dict,
ud_symtab = undef "symtab",
ud_put_name = undef "put_name",
ud_put_fs = undef "put_fs"
}
newWriteState :: (BinHandle -> Name -> IO ())
-> (BinHandle -> FastString -> IO ())
-> IO UserData
newWriteState put_name put_fs = do
return UserData { ud_dict = undef "dict",
ud_symtab = undef "symtab",
ud_put_name = put_name,
ud_put_fs = put_fs
}
noUserData :: a
noUserData = undef "UserData"
undef :: String -> a
undef s = panic ("Binary.UserData: no " ++ s)
type Dictionary = Array Int FastString
putDictionary :: BinHandle -> Int -> UniqFM (Int,FastString) -> IO ()
putDictionary bh sz dict = do
put_ bh sz
mapM_ (putFS bh) (elems (array (0,sz1) (eltsUFM dict)))
getDictionary :: BinHandle -> IO Dictionary
getDictionary bh = do
sz <- get bh
elems <- sequence (take sz (repeat (getFS bh)))
return (listArray (0,sz1) elems)
type SymbolTable = Array Int Name
putFS :: BinHandle -> FastString -> IO ()
putFS bh (FastString _ l _ buf _) = do
put_ bh l
withForeignPtr buf $ \ptr ->
let
go n | n == l = return ()
| otherwise = do
b <- peekElemOff ptr n
putByte bh b
go (n+1)
in
go 0
getFS :: BinHandle -> IO FastString
getFS bh = do
l <- get bh
fp <- mallocForeignPtrBytes l
withForeignPtr fp $ \ptr -> do
let
go n | n == l = mkFastStringForeignPtr ptr fp l
| otherwise = do
b <- getByte bh
pokeElemOff ptr n b
go (n+1)
go 0
instance Binary FastString where
put_ bh f =
case getUserData bh of
UserData { ud_put_fs = put_fs } -> put_fs bh f
get bh = do
j <- get bh
return $! (ud_dict (getUserData bh) ! (fromIntegral (j :: Word32)))
instance Binary Fingerprint where
put_ h (Fingerprint w1 w2) = do put_ h w1; put_ h w2
get h = do w1 <- get h; w2 <- get h; return (Fingerprint w1 w2)
instance Binary FunctionOrData where
put_ bh IsFunction = putByte bh 0
put_ bh IsData = putByte bh 1
get bh = do
h <- getByte bh
case h of
0 -> return IsFunction
1 -> return IsData
_ -> panic "Binary FunctionOrData"