PageRenderTime 68ms CodeModel.GetById 31ms RepoModel.GetById 0ms app.codeStats 0ms

/compiler/utils/Binary.hs

https://github.com/crdueck/ghc
Haskell | 927 lines | 675 code | 137 blank | 115 comment | 17 complexity | 791e2a2c4da83464aa3acbbf87d5d933 MD5 | raw file
  1. {-# OPTIONS -cpp #-}
  2. {-# OPTIONS_GHC -O -funbox-strict-fields #-}
  3. -- We always optimise this, otherwise performance of a non-optimised
  4. -- compiler is severely affected
  5. --
  6. -- (c) The University of Glasgow 2002-2006
  7. --
  8. -- Binary I/O library, with special tweaks for GHC
  9. --
  10. -- Based on the nhc98 Binary library, which is copyright
  11. -- (c) Malcolm Wallace and Colin Runciman, University of York, 1998.
  12. -- Under the terms of the license for that software, we must tell you
  13. -- where you can obtain the original version of the Binary library, namely
  14. -- http://www.cs.york.ac.uk/fp/nhc98/
  15. module Binary
  16. ( {-type-} Bin,
  17. {-class-} Binary(..),
  18. {-type-} BinHandle,
  19. SymbolTable, Dictionary,
  20. openBinIO, openBinIO_,
  21. openBinMem,
  22. -- closeBin,
  23. seekBin,
  24. seekBy,
  25. tellBin,
  26. castBin,
  27. writeBinMem,
  28. readBinMem,
  29. fingerprintBinMem,
  30. computeFingerprint,
  31. isEOFBin,
  32. putAt, getAt,
  33. -- for writing instances:
  34. putByte,
  35. getByte,
  36. -- lazy Bin I/O
  37. lazyGet,
  38. lazyPut,
  39. #ifdef __GLASGOW_HASKELL__
  40. -- GHC only:
  41. ByteArray(..),
  42. getByteArray,
  43. putByteArray,
  44. #endif
  45. UserData(..), getUserData, setUserData,
  46. newReadState, newWriteState,
  47. putDictionary, getDictionary, putFS,
  48. ) where
  49. #include "HsVersions.h"
  50. -- The *host* architecture version:
  51. #include "../includes/MachDeps.h"
  52. import {-# SOURCE #-} Name (Name)
  53. import FastString
  54. import Panic
  55. import UniqFM
  56. import FastMutInt
  57. import Fingerprint
  58. import BasicTypes
  59. import Foreign
  60. import Data.Array
  61. import Data.ByteString (ByteString)
  62. import qualified Data.ByteString.Internal as BS
  63. import qualified Data.ByteString.Unsafe as BS
  64. import Data.IORef
  65. import Data.Char ( ord, chr )
  66. import Data.Time
  67. import Data.Typeable
  68. import Data.Typeable.Internal
  69. import Control.Monad ( when )
  70. import System.IO as IO
  71. import System.IO.Unsafe ( unsafeInterleaveIO )
  72. import System.IO.Error ( mkIOError, eofErrorType )
  73. import GHC.Real ( Ratio(..) )
  74. import GHC.Exts
  75. import GHC.Word ( Word8(..) )
  76. import GHC.IO ( IO(..) )
  77. type BinArray = ForeignPtr Word8
  78. ---------------------------------------------------------------
  79. -- BinHandle
  80. ---------------------------------------------------------------
  81. data BinHandle
  82. = BinMem { -- binary data stored in an unboxed array
  83. bh_usr :: UserData, -- sigh, need parameterized modules :-)
  84. _off_r :: !FastMutInt, -- the current offset
  85. _sz_r :: !FastMutInt, -- size of the array (cached)
  86. _arr_r :: !(IORef BinArray) -- the array (bounds: (0,size-1))
  87. }
  88. -- XXX: should really store a "high water mark" for dumping out
  89. -- the binary data to a file.
  90. | BinIO { -- binary data stored in a file
  91. bh_usr :: UserData,
  92. _off_r :: !FastMutInt, -- the current offset (cached)
  93. _hdl :: !IO.Handle -- the file handle (must be seekable)
  94. }
  95. -- cache the file ptr in BinIO; using hTell is too expensive
  96. -- to call repeatedly. If anyone else is modifying this Handle
  97. -- at the same time, we'll be screwed.
  98. getUserData :: BinHandle -> UserData
  99. getUserData bh = bh_usr bh
  100. setUserData :: BinHandle -> UserData -> BinHandle
  101. setUserData bh us = bh { bh_usr = us }
  102. ---------------------------------------------------------------
  103. -- Bin
  104. ---------------------------------------------------------------
  105. newtype Bin a = BinPtr Int
  106. deriving (Eq, Ord, Show, Bounded)
  107. castBin :: Bin a -> Bin b
  108. castBin (BinPtr i) = BinPtr i
  109. ---------------------------------------------------------------
  110. -- class Binary
  111. ---------------------------------------------------------------
  112. class Binary a where
  113. put_ :: BinHandle -> a -> IO ()
  114. put :: BinHandle -> a -> IO (Bin a)
  115. get :: BinHandle -> IO a
  116. -- define one of put_, put. Use of put_ is recommended because it
  117. -- is more likely that tail-calls can kick in, and we rarely need the
  118. -- position return value.
  119. put_ bh a = do _ <- put bh a; return ()
  120. put bh a = do p <- tellBin bh; put_ bh a; return p
  121. putAt :: Binary a => BinHandle -> Bin a -> a -> IO ()
  122. putAt bh p x = do seekBin bh p; put_ bh x; return ()
  123. getAt :: Binary a => BinHandle -> Bin a -> IO a
  124. getAt bh p = do seekBin bh p; get bh
  125. openBinIO_ :: IO.Handle -> IO BinHandle
  126. openBinIO_ h = openBinIO h
  127. openBinIO :: IO.Handle -> IO BinHandle
  128. openBinIO h = do
  129. r <- newFastMutInt
  130. writeFastMutInt r 0
  131. return (BinIO noUserData r h)
  132. openBinMem :: Int -> IO BinHandle
  133. openBinMem size
  134. | size <= 0 = error "Data.Binary.openBinMem: size must be >= 0"
  135. | otherwise = do
  136. arr <- mallocForeignPtrBytes size
  137. arr_r <- newIORef arr
  138. ix_r <- newFastMutInt
  139. writeFastMutInt ix_r 0
  140. sz_r <- newFastMutInt
  141. writeFastMutInt sz_r size
  142. return (BinMem noUserData ix_r sz_r arr_r)
  143. tellBin :: BinHandle -> IO (Bin a)
  144. tellBin (BinIO _ r _) = do ix <- readFastMutInt r; return (BinPtr ix)
  145. tellBin (BinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix)
  146. seekBin :: BinHandle -> Bin a -> IO ()
  147. seekBin (BinIO _ ix_r h) (BinPtr p) = do
  148. writeFastMutInt ix_r p
  149. hSeek h AbsoluteSeek (fromIntegral p)
  150. seekBin h@(BinMem _ ix_r sz_r _) (BinPtr p) = do
  151. sz <- readFastMutInt sz_r
  152. if (p >= sz)
  153. then do expandBin h p; writeFastMutInt ix_r p
  154. else writeFastMutInt ix_r p
  155. seekBy :: BinHandle -> Int -> IO ()
  156. seekBy (BinIO _ ix_r h) off = do
  157. ix <- readFastMutInt ix_r
  158. let ix' = ix + off
  159. writeFastMutInt ix_r ix'
  160. hSeek h AbsoluteSeek (fromIntegral ix')
  161. seekBy h@(BinMem _ ix_r sz_r _) off = do
  162. sz <- readFastMutInt sz_r
  163. ix <- readFastMutInt ix_r
  164. let ix' = ix + off
  165. if (ix' >= sz)
  166. then do expandBin h ix'; writeFastMutInt ix_r ix'
  167. else writeFastMutInt ix_r ix'
  168. isEOFBin :: BinHandle -> IO Bool
  169. isEOFBin (BinMem _ ix_r sz_r _) = do
  170. ix <- readFastMutInt ix_r
  171. sz <- readFastMutInt sz_r
  172. return (ix >= sz)
  173. isEOFBin (BinIO _ _ h) = hIsEOF h
  174. writeBinMem :: BinHandle -> FilePath -> IO ()
  175. writeBinMem (BinIO _ _ _) _ = error "Data.Binary.writeBinMem: not a memory handle"
  176. writeBinMem (BinMem _ ix_r _ arr_r) fn = do
  177. h <- openBinaryFile fn WriteMode
  178. arr <- readIORef arr_r
  179. ix <- readFastMutInt ix_r
  180. withForeignPtr arr $ \p -> hPutBuf h p ix
  181. hClose h
  182. readBinMem :: FilePath -> IO BinHandle
  183. -- Return a BinHandle with a totally undefined State
  184. readBinMem filename = do
  185. h <- openBinaryFile filename ReadMode
  186. filesize' <- hFileSize h
  187. let filesize = fromIntegral filesize'
  188. arr <- mallocForeignPtrBytes (filesize*2)
  189. count <- withForeignPtr arr $ \p -> hGetBuf h p filesize
  190. when (count /= filesize) $
  191. error ("Binary.readBinMem: only read " ++ show count ++ " bytes")
  192. hClose h
  193. arr_r <- newIORef arr
  194. ix_r <- newFastMutInt
  195. writeFastMutInt ix_r 0
  196. sz_r <- newFastMutInt
  197. writeFastMutInt sz_r filesize
  198. return (BinMem noUserData ix_r sz_r arr_r)
  199. fingerprintBinMem :: BinHandle -> IO Fingerprint
  200. fingerprintBinMem (BinIO _ _ _) = error "Binary.md5BinMem: not a memory handle"
  201. fingerprintBinMem (BinMem _ ix_r _ arr_r) = do
  202. arr <- readIORef arr_r
  203. ix <- readFastMutInt ix_r
  204. withForeignPtr arr $ \p -> fingerprintData p ix
  205. computeFingerprint :: Binary a
  206. => (BinHandle -> Name -> IO ())
  207. -> a
  208. -> IO Fingerprint
  209. computeFingerprint put_name a = do
  210. bh <- openBinMem (3*1024) -- just less than a block
  211. bh <- return $ setUserData bh $ newWriteState put_name putFS
  212. put_ bh a
  213. fingerprintBinMem bh
  214. -- expand the size of the array to include a specified offset
  215. expandBin :: BinHandle -> Int -> IO ()
  216. expandBin (BinMem _ _ sz_r arr_r) off = do
  217. sz <- readFastMutInt sz_r
  218. let sz' = head (dropWhile (<= off) (iterate (* 2) sz))
  219. arr <- readIORef arr_r
  220. arr' <- mallocForeignPtrBytes sz'
  221. withForeignPtr arr $ \old ->
  222. withForeignPtr arr' $ \new ->
  223. copyBytes new old sz
  224. writeFastMutInt sz_r sz'
  225. writeIORef arr_r arr'
  226. expandBin (BinIO _ _ _) _ = return ()
  227. -- no need to expand a file, we'll assume they expand by themselves.
  228. -- -----------------------------------------------------------------------------
  229. -- Low-level reading/writing of bytes
  230. putWord8 :: BinHandle -> Word8 -> IO ()
  231. putWord8 h@(BinMem _ ix_r sz_r arr_r) w = do
  232. ix <- readFastMutInt ix_r
  233. sz <- readFastMutInt sz_r
  234. -- double the size of the array if it overflows
  235. if (ix >= sz)
  236. then do expandBin h ix
  237. putWord8 h w
  238. else do arr <- readIORef arr_r
  239. withForeignPtr arr $ \p -> pokeByteOff p ix w
  240. writeFastMutInt ix_r (ix+1)
  241. return ()
  242. putWord8 (BinIO _ ix_r h) w = do
  243. ix <- readFastMutInt ix_r
  244. hPutChar h (chr (fromIntegral w)) -- XXX not really correct
  245. writeFastMutInt ix_r (ix+1)
  246. return ()
  247. getWord8 :: BinHandle -> IO Word8
  248. getWord8 (BinMem _ ix_r sz_r arr_r) = do
  249. ix <- readFastMutInt ix_r
  250. sz <- readFastMutInt sz_r
  251. when (ix >= sz) $
  252. ioError (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
  253. arr <- readIORef arr_r
  254. w <- withForeignPtr arr $ \p -> peekByteOff p ix
  255. writeFastMutInt ix_r (ix+1)
  256. return w
  257. getWord8 (BinIO _ ix_r h) = do
  258. ix <- readFastMutInt ix_r
  259. c <- hGetChar h
  260. writeFastMutInt ix_r (ix+1)
  261. return $! (fromIntegral (ord c)) -- XXX not really correct
  262. putByte :: BinHandle -> Word8 -> IO ()
  263. putByte bh w = put_ bh w
  264. getByte :: BinHandle -> IO Word8
  265. getByte = getWord8
  266. -- -----------------------------------------------------------------------------
  267. -- Primitve Word writes
  268. instance Binary Word8 where
  269. put_ = putWord8
  270. get = getWord8
  271. instance Binary Word16 where
  272. put_ h w = do -- XXX too slow.. inline putWord8?
  273. putByte h (fromIntegral (w `shiftR` 8))
  274. putByte h (fromIntegral (w .&. 0xff))
  275. get h = do
  276. w1 <- getWord8 h
  277. w2 <- getWord8 h
  278. return $! ((fromIntegral w1 `shiftL` 8) .|. fromIntegral w2)
  279. instance Binary Word32 where
  280. put_ h w = do
  281. putByte h (fromIntegral (w `shiftR` 24))
  282. putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
  283. putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff))
  284. putByte h (fromIntegral (w .&. 0xff))
  285. get h = do
  286. w1 <- getWord8 h
  287. w2 <- getWord8 h
  288. w3 <- getWord8 h
  289. w4 <- getWord8 h
  290. return $! ((fromIntegral w1 `shiftL` 24) .|.
  291. (fromIntegral w2 `shiftL` 16) .|.
  292. (fromIntegral w3 `shiftL` 8) .|.
  293. (fromIntegral w4))
  294. instance Binary Word64 where
  295. put_ h w = do
  296. putByte h (fromIntegral (w `shiftR` 56))
  297. putByte h (fromIntegral ((w `shiftR` 48) .&. 0xff))
  298. putByte h (fromIntegral ((w `shiftR` 40) .&. 0xff))
  299. putByte h (fromIntegral ((w `shiftR` 32) .&. 0xff))
  300. putByte h (fromIntegral ((w `shiftR` 24) .&. 0xff))
  301. putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
  302. putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff))
  303. putByte h (fromIntegral (w .&. 0xff))
  304. get h = do
  305. w1 <- getWord8 h
  306. w2 <- getWord8 h
  307. w3 <- getWord8 h
  308. w4 <- getWord8 h
  309. w5 <- getWord8 h
  310. w6 <- getWord8 h
  311. w7 <- getWord8 h
  312. w8 <- getWord8 h
  313. return $! ((fromIntegral w1 `shiftL` 56) .|.
  314. (fromIntegral w2 `shiftL` 48) .|.
  315. (fromIntegral w3 `shiftL` 40) .|.
  316. (fromIntegral w4 `shiftL` 32) .|.
  317. (fromIntegral w5 `shiftL` 24) .|.
  318. (fromIntegral w6 `shiftL` 16) .|.
  319. (fromIntegral w7 `shiftL` 8) .|.
  320. (fromIntegral w8))
  321. -- -----------------------------------------------------------------------------
  322. -- Primitve Int writes
  323. instance Binary Int8 where
  324. put_ h w = put_ h (fromIntegral w :: Word8)
  325. get h = do w <- get h; return $! (fromIntegral (w::Word8))
  326. instance Binary Int16 where
  327. put_ h w = put_ h (fromIntegral w :: Word16)
  328. get h = do w <- get h; return $! (fromIntegral (w::Word16))
  329. instance Binary Int32 where
  330. put_ h w = put_ h (fromIntegral w :: Word32)
  331. get h = do w <- get h; return $! (fromIntegral (w::Word32))
  332. instance Binary Int64 where
  333. put_ h w = put_ h (fromIntegral w :: Word64)
  334. get h = do w <- get h; return $! (fromIntegral (w::Word64))
  335. -- -----------------------------------------------------------------------------
  336. -- Instances for standard types
  337. instance Binary () where
  338. put_ _ () = return ()
  339. get _ = return ()
  340. instance Binary Bool where
  341. put_ bh b = putByte bh (fromIntegral (fromEnum b))
  342. get bh = do x <- getWord8 bh; return $! (toEnum (fromIntegral x))
  343. instance Binary Char where
  344. put_ bh c = put_ bh (fromIntegral (ord c) :: Word32)
  345. get bh = do x <- get bh; return $! (chr (fromIntegral (x :: Word32)))
  346. instance Binary Int where
  347. put_ bh i = put_ bh (fromIntegral i :: Int64)
  348. get bh = do
  349. x <- get bh
  350. return $! (fromIntegral (x :: Int64))
  351. instance Binary a => Binary [a] where
  352. put_ bh l = do
  353. let len = length l
  354. if (len < 0xff)
  355. then putByte bh (fromIntegral len :: Word8)
  356. else do putByte bh 0xff; put_ bh (fromIntegral len :: Word32)
  357. mapM_ (put_ bh) l
  358. get bh = do
  359. b <- getByte bh
  360. len <- if b == 0xff
  361. then get bh
  362. else return (fromIntegral b :: Word32)
  363. let loop 0 = return []
  364. loop n = do a <- get bh; as <- loop (n-1); return (a:as)
  365. loop len
  366. instance (Binary a, Binary b) => Binary (a,b) where
  367. put_ bh (a,b) = do put_ bh a; put_ bh b
  368. get bh = do a <- get bh
  369. b <- get bh
  370. return (a,b)
  371. instance (Binary a, Binary b, Binary c) => Binary (a,b,c) where
  372. put_ bh (a,b,c) = do put_ bh a; put_ bh b; put_ bh c
  373. get bh = do a <- get bh
  374. b <- get bh
  375. c <- get bh
  376. return (a,b,c)
  377. instance (Binary a, Binary b, Binary c, Binary d) => Binary (a,b,c,d) where
  378. put_ bh (a,b,c,d) = do put_ bh a; put_ bh b; put_ bh c; put_ bh d
  379. get bh = do a <- get bh
  380. b <- get bh
  381. c <- get bh
  382. d <- get bh
  383. return (a,b,c,d)
  384. instance (Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a,b,c,d, e) where
  385. put_ bh (a,b,c,d, e) = do put_ bh a; put_ bh b; put_ bh c; put_ bh d; put_ bh e;
  386. get bh = do a <- get bh
  387. b <- get bh
  388. c <- get bh
  389. d <- get bh
  390. e <- get bh
  391. return (a,b,c,d,e)
  392. instance (Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a,b,c,d, e, f) where
  393. put_ bh (a,b,c,d, e, f) = do put_ bh a; put_ bh b; put_ bh c; put_ bh d; put_ bh e; put_ bh f;
  394. get bh = do a <- get bh
  395. b <- get bh
  396. c <- get bh
  397. d <- get bh
  398. e <- get bh
  399. f <- get bh
  400. return (a,b,c,d,e,f)
  401. instance Binary a => Binary (Maybe a) where
  402. put_ bh Nothing = putByte bh 0
  403. put_ bh (Just a) = do putByte bh 1; put_ bh a
  404. get bh = do h <- getWord8 bh
  405. case h of
  406. 0 -> return Nothing
  407. _ -> do x <- get bh; return (Just x)
  408. instance (Binary a, Binary b) => Binary (Either a b) where
  409. put_ bh (Left a) = do putByte bh 0; put_ bh a
  410. put_ bh (Right b) = do putByte bh 1; put_ bh b
  411. get bh = do h <- getWord8 bh
  412. case h of
  413. 0 -> do a <- get bh ; return (Left a)
  414. _ -> do b <- get bh ; return (Right b)
  415. instance Binary UTCTime where
  416. put_ bh u = do put_ bh (utctDay u)
  417. put_ bh (utctDayTime u)
  418. get bh = do day <- get bh
  419. dayTime <- get bh
  420. return $ UTCTime { utctDay = day, utctDayTime = dayTime }
  421. instance Binary Day where
  422. put_ bh d = put_ bh (toModifiedJulianDay d)
  423. get bh = do i <- get bh
  424. return $ ModifiedJulianDay { toModifiedJulianDay = i }
  425. instance Binary DiffTime where
  426. put_ bh dt = put_ bh (toRational dt)
  427. get bh = do r <- get bh
  428. return $ fromRational r
  429. #if defined(__GLASGOW_HASKELL__) || 1
  430. --to quote binary-0.3 on this code idea,
  431. --
  432. -- TODO This instance is not architecture portable. GMP stores numbers as
  433. -- arrays of machine sized words, so the byte format is not portable across
  434. -- architectures with different endianess and word size.
  435. --
  436. -- This makes it hard (impossible) to make an equivalent instance
  437. -- with code that is compilable with non-GHC. Do we need any instance
  438. -- Binary Integer, and if so, does it have to be blazing fast? Or can
  439. -- we just change this instance to be portable like the rest of the
  440. -- instances? (binary package has code to steal for that)
  441. --
  442. -- yes, we need Binary Integer and Binary Rational in basicTypes/Literal.lhs
  443. instance Binary Integer where
  444. -- XXX This is hideous
  445. put_ bh i = put_ bh (show i)
  446. get bh = do str <- get bh
  447. case reads str of
  448. [(i, "")] -> return i
  449. _ -> fail ("Binary Integer: got " ++ show str)
  450. {-
  451. put_ bh (S# i#) = do putByte bh 0; put_ bh (I# i#)
  452. put_ bh (J# s# a#) = do
  453. putByte bh 1
  454. put_ bh (I# s#)
  455. let sz# = sizeofByteArray# a# -- in *bytes*
  456. put_ bh (I# sz#) -- in *bytes*
  457. putByteArray bh a# sz#
  458. get bh = do
  459. b <- getByte bh
  460. case b of
  461. 0 -> do (I# i#) <- get bh
  462. return (S# i#)
  463. _ -> do (I# s#) <- get bh
  464. sz <- get bh
  465. (BA a#) <- getByteArray bh sz
  466. return (J# s# a#)
  467. -}
  468. -- As for the rest of this code, even though this module
  469. -- exports it, it doesn't seem to be used anywhere else
  470. -- in GHC!
  471. putByteArray :: BinHandle -> ByteArray# -> Int# -> IO ()
  472. putByteArray bh a s# = loop 0#
  473. where loop n#
  474. | n# ==# s# = return ()
  475. | otherwise = do
  476. putByte bh (indexByteArray a n#)
  477. loop (n# +# 1#)
  478. getByteArray :: BinHandle -> Int -> IO ByteArray
  479. getByteArray bh (I# sz) = do
  480. (MBA arr) <- newByteArray sz
  481. let loop n
  482. | n ==# sz = return ()
  483. | otherwise = do
  484. w <- getByte bh
  485. writeByteArray arr n w
  486. loop (n +# 1#)
  487. loop 0#
  488. freezeByteArray arr
  489. data ByteArray = BA ByteArray#
  490. data MBA = MBA (MutableByteArray# RealWorld)
  491. newByteArray :: Int# -> IO MBA
  492. newByteArray sz = IO $ \s ->
  493. case newByteArray# sz s of { (# s, arr #) ->
  494. (# s, MBA arr #) }
  495. freezeByteArray :: MutableByteArray# RealWorld -> IO ByteArray
  496. freezeByteArray arr = IO $ \s ->
  497. case unsafeFreezeByteArray# arr s of { (# s, arr #) ->
  498. (# s, BA arr #) }
  499. writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO ()
  500. writeByteArray arr i (W8# w) = IO $ \s ->
  501. case writeWord8Array# arr i w s of { s ->
  502. (# s, () #) }
  503. indexByteArray :: ByteArray# -> Int# -> Word8
  504. indexByteArray a# n# = W8# (indexWord8Array# a# n#)
  505. instance (Integral a, Binary a) => Binary (Ratio a) where
  506. put_ bh (a :% b) = do put_ bh a; put_ bh b
  507. get bh = do a <- get bh; b <- get bh; return (a :% b)
  508. #endif
  509. instance Binary (Bin a) where
  510. put_ bh (BinPtr i) = put_ bh (fromIntegral i :: Int32)
  511. get bh = do i <- get bh; return (BinPtr (fromIntegral (i :: Int32)))
  512. -- -----------------------------------------------------------------------------
  513. -- Instances for Data.Typeable stuff
  514. instance Binary TyCon where
  515. put_ bh (TyCon _ p m n) = do
  516. put_ bh (p,m,n)
  517. get bh = do
  518. (p,m,n) <- get bh
  519. return (mkTyCon3 p m n)
  520. instance Binary TypeRep where
  521. put_ bh type_rep = do
  522. let (ty_con, child_type_reps) = splitTyConApp type_rep
  523. put_ bh ty_con
  524. put_ bh child_type_reps
  525. get bh = do
  526. ty_con <- get bh
  527. child_type_reps <- get bh
  528. return (mkTyConApp ty_con child_type_reps)
  529. -- -----------------------------------------------------------------------------
  530. -- Lazy reading/writing
  531. lazyPut :: Binary a => BinHandle -> a -> IO ()
  532. lazyPut bh a = do
  533. -- output the obj with a ptr to skip over it:
  534. pre_a <- tellBin bh
  535. put_ bh pre_a -- save a slot for the ptr
  536. put_ bh a -- dump the object
  537. q <- tellBin bh -- q = ptr to after object
  538. putAt bh pre_a q -- fill in slot before a with ptr to q
  539. seekBin bh q -- finally carry on writing at q
  540. lazyGet :: Binary a => BinHandle -> IO a
  541. lazyGet bh = do
  542. p <- get bh -- a BinPtr
  543. p_a <- tellBin bh
  544. a <- unsafeInterleaveIO (getAt bh p_a)
  545. seekBin bh p -- skip over the object for now
  546. return a
  547. -- -----------------------------------------------------------------------------
  548. -- UserData
  549. -- -----------------------------------------------------------------------------
  550. data UserData =
  551. UserData {
  552. -- for *deserialising* only:
  553. ud_get_name :: BinHandle -> IO Name,
  554. ud_get_fs :: BinHandle -> IO FastString,
  555. -- for *serialising* only:
  556. ud_put_name :: BinHandle -> Name -> IO (),
  557. ud_put_fs :: BinHandle -> FastString -> IO ()
  558. }
  559. newReadState :: (BinHandle -> IO Name)
  560. -> (BinHandle -> IO FastString)
  561. -> UserData
  562. newReadState get_name get_fs
  563. = UserData { ud_get_name = get_name,
  564. ud_get_fs = get_fs,
  565. ud_put_name = undef "put_name",
  566. ud_put_fs = undef "put_fs"
  567. }
  568. newWriteState :: (BinHandle -> Name -> IO ())
  569. -> (BinHandle -> FastString -> IO ())
  570. -> UserData
  571. newWriteState put_name put_fs
  572. = UserData { ud_get_name = undef "get_name",
  573. ud_get_fs = undef "get_fs",
  574. ud_put_name = put_name,
  575. ud_put_fs = put_fs
  576. }
  577. noUserData :: a
  578. noUserData = undef "UserData"
  579. undef :: String -> a
  580. undef s = panic ("Binary.UserData: no " ++ s)
  581. ---------------------------------------------------------
  582. -- The Dictionary
  583. ---------------------------------------------------------
  584. type Dictionary = Array Int FastString -- The dictionary
  585. -- Should be 0-indexed
  586. putDictionary :: BinHandle -> Int -> UniqFM (Int,FastString) -> IO ()
  587. putDictionary bh sz dict = do
  588. put_ bh sz
  589. mapM_ (putFS bh) (elems (array (0,sz-1) (eltsUFM dict)))
  590. getDictionary :: BinHandle -> IO Dictionary
  591. getDictionary bh = do
  592. sz <- get bh
  593. elems <- sequence (take sz (repeat (getFS bh)))
  594. return (listArray (0,sz-1) elems)
  595. ---------------------------------------------------------
  596. -- The Symbol Table
  597. ---------------------------------------------------------
  598. -- On disk, the symbol table is an array of IfaceExtName, when
  599. -- reading it in we turn it into a SymbolTable.
  600. type SymbolTable = Array Int Name
  601. ---------------------------------------------------------
  602. -- Reading and writing FastStrings
  603. ---------------------------------------------------------
  604. putFS :: BinHandle -> FastString -> IO ()
  605. putFS bh fs = putBS bh $ fastStringToByteString fs
  606. getFS :: BinHandle -> IO FastString
  607. getFS bh = do bs <- getBS bh
  608. mkFastStringByteString bs
  609. putBS :: BinHandle -> ByteString -> IO ()
  610. putBS bh bs =
  611. BS.unsafeUseAsCStringLen bs $ \(ptr, l) -> do
  612. put_ bh l
  613. let
  614. go n | n == l = return ()
  615. | otherwise = do
  616. b <- peekElemOff (castPtr ptr) n
  617. putByte bh b
  618. go (n+1)
  619. go 0
  620. {- -- possible faster version, not quite there yet:
  621. getBS bh@BinMem{} = do
  622. (I# l) <- get bh
  623. arr <- readIORef (arr_r bh)
  624. off <- readFastMutInt (off_r bh)
  625. return $! (mkFastSubBytesBA# arr off l)
  626. -}
  627. getBS :: BinHandle -> IO ByteString
  628. getBS bh = do
  629. l <- get bh
  630. fp <- mallocForeignPtrBytes l
  631. withForeignPtr fp $ \ptr -> do
  632. let
  633. go n | n == l = return $ BS.fromForeignPtr fp 0 l
  634. | otherwise = do
  635. b <- getByte bh
  636. pokeElemOff ptr n b
  637. go (n+1)
  638. --
  639. go 0
  640. instance Binary ByteString where
  641. put_ bh f = putBS bh f
  642. get bh = getBS bh
  643. instance Binary FastString where
  644. put_ bh f =
  645. case getUserData bh of
  646. UserData { ud_put_fs = put_fs } -> put_fs bh f
  647. get bh =
  648. case getUserData bh of
  649. UserData { ud_get_fs = get_fs } -> get_fs bh
  650. -- Here to avoid loop
  651. instance Binary Fingerprint where
  652. put_ h (Fingerprint w1 w2) = do put_ h w1; put_ h w2
  653. get h = do w1 <- get h; w2 <- get h; return (Fingerprint w1 w2)
  654. instance Binary FunctionOrData where
  655. put_ bh IsFunction = putByte bh 0
  656. put_ bh IsData = putByte bh 1
  657. get bh = do
  658. h <- getByte bh
  659. case h of
  660. 0 -> return IsFunction
  661. 1 -> return IsData
  662. _ -> panic "Binary FunctionOrData"
  663. instance Binary TupleSort where
  664. put_ bh BoxedTuple = putByte bh 0
  665. put_ bh UnboxedTuple = putByte bh 1
  666. put_ bh ConstraintTuple = putByte bh 2
  667. get bh = do
  668. h <- getByte bh
  669. case h of
  670. 0 -> do return BoxedTuple
  671. 1 -> do return UnboxedTuple
  672. _ -> do return ConstraintTuple
  673. instance Binary Activation where
  674. put_ bh NeverActive = do
  675. putByte bh 0
  676. put_ bh AlwaysActive = do
  677. putByte bh 1
  678. put_ bh (ActiveBefore aa) = do
  679. putByte bh 2
  680. put_ bh aa
  681. put_ bh (ActiveAfter ab) = do
  682. putByte bh 3
  683. put_ bh ab
  684. get bh = do
  685. h <- getByte bh
  686. case h of
  687. 0 -> do return NeverActive
  688. 1 -> do return AlwaysActive
  689. 2 -> do aa <- get bh
  690. return (ActiveBefore aa)
  691. _ -> do ab <- get bh
  692. return (ActiveAfter ab)
  693. instance Binary InlinePragma where
  694. put_ bh (InlinePragma a b c d) = do
  695. put_ bh a
  696. put_ bh b
  697. put_ bh c
  698. put_ bh d
  699. get bh = do
  700. a <- get bh
  701. b <- get bh
  702. c <- get bh
  703. d <- get bh
  704. return (InlinePragma a b c d)
  705. instance Binary RuleMatchInfo where
  706. put_ bh FunLike = putByte bh 0
  707. put_ bh ConLike = putByte bh 1
  708. get bh = do
  709. h <- getByte bh
  710. if h == 1 then return ConLike
  711. else return FunLike
  712. instance Binary InlineSpec where
  713. put_ bh EmptyInlineSpec = putByte bh 0
  714. put_ bh Inline = putByte bh 1
  715. put_ bh Inlinable = putByte bh 2
  716. put_ bh NoInline = putByte bh 3
  717. get bh = do h <- getByte bh
  718. case h of
  719. 0 -> return EmptyInlineSpec
  720. 1 -> return Inline
  721. 2 -> return Inlinable
  722. _ -> return NoInline
  723. instance Binary DefMethSpec where
  724. put_ bh NoDM = putByte bh 0
  725. put_ bh VanillaDM = putByte bh 1
  726. put_ bh GenericDM = putByte bh 2
  727. get bh = do
  728. h <- getByte bh
  729. case h of
  730. 0 -> return NoDM
  731. 1 -> return VanillaDM
  732. _ -> return GenericDM
  733. instance Binary RecFlag where
  734. put_ bh Recursive = do
  735. putByte bh 0
  736. put_ bh NonRecursive = do
  737. putByte bh 1
  738. get bh = do
  739. h <- getByte bh
  740. case h of
  741. 0 -> do return Recursive
  742. _ -> do return NonRecursive
  743. instance Binary OverlapFlag where
  744. put_ bh (NoOverlap b) = putByte bh 0 >> put_ bh b
  745. put_ bh (OverlapOk b) = putByte bh 1 >> put_ bh b
  746. put_ bh (Incoherent b) = putByte bh 2 >> put_ bh b
  747. get bh = do
  748. h <- getByte bh
  749. b <- get bh
  750. case h of
  751. 0 -> return $ NoOverlap b
  752. 1 -> return $ OverlapOk b
  753. 2 -> return $ Incoherent b
  754. _ -> panic ("get OverlapFlag " ++ show h)
  755. instance Binary FixityDirection where
  756. put_ bh InfixL = do
  757. putByte bh 0
  758. put_ bh InfixR = do
  759. putByte bh 1
  760. put_ bh InfixN = do
  761. putByte bh 2
  762. get bh = do
  763. h <- getByte bh
  764. case h of
  765. 0 -> do return InfixL
  766. 1 -> do return InfixR
  767. _ -> do return InfixN
  768. instance Binary Fixity where
  769. put_ bh (Fixity aa ab) = do
  770. put_ bh aa
  771. put_ bh ab
  772. get bh = do
  773. aa <- get bh
  774. ab <- get bh
  775. return (Fixity aa ab)
  776. instance Binary WarningTxt where
  777. put_ bh (WarningTxt w) = do
  778. putByte bh 0
  779. put_ bh w
  780. put_ bh (DeprecatedTxt d) = do
  781. putByte bh 1
  782. put_ bh d
  783. get bh = do
  784. h <- getByte bh
  785. case h of
  786. 0 -> do w <- get bh
  787. return (WarningTxt w)
  788. _ -> do d <- get bh
  789. return (DeprecatedTxt d)