[project @ 2003-10-09 11:58:39 by simonpj]
[ghc-hetmet.git] / ghc / compiler / utils / Binary.hs
1 {-# OPTIONS -cpp #-}
2 --
3 -- (c) The University of Glasgow 2002
4 --
5 -- Binary I/O library, with special tweaks for GHC
6 --
7 -- Based on the nhc98 Binary library, which is copyright
8 -- (c) Malcolm Wallace and Colin Runciman, University of York, 1998.
9 -- Under the terms of the license for that software, we must tell you
10 -- where you can obtain the original version of the Binary library, namely
11 --     http://www.cs.york.ac.uk/fp/nhc98/
12
13 module Binary
14   ( {-type-}  Bin,
15     {-class-} Binary(..),
16     {-type-}  BinHandle,
17
18    openBinIO, openBinIO_,
19    openBinMem,
20 --   closeBin,
21
22    seekBin,
23    tellBin,
24    castBin,
25
26    writeBinMem,
27    readBinMem,
28
29    isEOFBin,
30
31    -- for writing instances:
32    putByte,
33    getByte,
34
35    -- lazy Bin I/O
36    lazyGet,
37    lazyPut,
38
39    -- GHC only:
40    ByteArray(..),
41    getByteArray,
42    putByteArray,
43
44    getBinFileWithDict,  -- :: Binary a => FilePath -> IO a
45    putBinFileWithDict,  -- :: Binary a => FilePath -> ModuleName -> a -> IO ()
46
47   ) where
48
49 #include "HsVersions.h"
50
51 -- The *host* architecture version:
52 #include "MachDeps.h"
53
54 import FastString
55 import Unique
56 import Panic
57 import UniqFM
58 import FastMutInt
59
60 #if __GLASGOW_HASKELL__ < 503
61 import DATA_IOREF
62 import DATA_BITS
63 import DATA_INT
64 import DATA_WORD
65 import Char
66 import Monad
67 import Exception
68 import GlaExts hiding (ByteArray, newByteArray, freezeByteArray)
69 import Array
70 import IO
71 import PrelIOBase               ( IOError(..), IOErrorType(..)
72 #if __GLASGOW_HASKELL__ > 411
73                                 , IOException(..)
74 #endif
75                                 )
76 import PrelReal                 ( Ratio(..) )
77 import PrelIOBase               ( IO(..) )
78 import IOExts                   ( openFileEx, IOModeEx(..) )
79 #else
80 import Data.Array.IO
81 import Data.Array
82 import Data.Bits
83 import Data.Int
84 import Data.Word
85 import Data.IORef
86 import Data.Char                ( ord, chr )
87 import Data.Array.Base          ( unsafeRead, unsafeWrite )
88 import Control.Monad            ( when )
89 import Control.Exception        ( throwDyn )
90 import System.IO as IO
91 import System.IO.Unsafe         ( unsafeInterleaveIO )
92 import System.IO.Error          ( mkIOError, eofErrorType )
93 import GHC.Real                 ( Ratio(..) )
94 import GHC.Exts
95 import GHC.IOBase               ( IO(..) )
96 import GHC.Word                 ( Word8(..) )
97 #if __GLASGOW_HASKELL__ < 601
98 -- openFileEx is available from the lang package, but we want to 
99 -- be independent of hslibs libraries.
100 import GHC.Handle               ( openFileEx, IOModeEx(..) )
101 #else
102 import System.IO                ( openBinaryFile )
103 #endif
104 #endif
105
106 #if __GLASGOW_HASKELL__ < 601
107 openBinaryFile f mode = openFileEx f (BinaryMode mode)
108 #endif
109
110 #if __GLASGOW_HASKELL__ < 503
111 type BinArray = MutableByteArray RealWorld Int
112 newArray_ bounds     = stToIO (newCharArray bounds)
113 unsafeWrite arr ix e = stToIO (writeWord8Array arr ix e)
114 unsafeRead  arr ix   = stToIO (readWord8Array arr ix)
115 #if __GLASGOW_HASKELL__ < 411
116 newByteArray#        = newCharArray#
117 #endif
118 hPutArray h arr sz   = hPutBufBAFull h arr sz
119 hGetArray h sz       = hGetBufBAFull h sz
120
121 mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> Exception
122 mkIOError t location maybe_hdl maybe_filename
123   = IOException (IOError maybe_hdl t location ""
124 #if __GLASGOW_HASKELL__ > 411
125                          maybe_filename
126 #endif
127                 )
128
129 eofErrorType = EOF
130
131 #ifndef SIZEOF_HSINT
132 #define SIZEOF_HSINT  INT_SIZE_IN_BYTES
133 #endif
134
135 #ifndef SIZEOF_HSWORD
136 #define SIZEOF_HSWORD WORD_SIZE_IN_BYTES
137 #endif
138
139 #else
140 type BinArray = IOUArray Int Word8
141 #endif
142
143 ---------------------------------------------------------------
144 --              BinHandle
145 ---------------------------------------------------------------
146
147 data BinHandle
148   = BinMem {            -- binary data stored in an unboxed array
149      bh_usr :: UserData,        -- sigh, need parameterized modules :-)
150      off_r :: !FastMutInt,              -- the current offset
151      sz_r  :: !FastMutInt,              -- size of the array (cached)
152      arr_r :: !(IORef BinArray)         -- the array (bounds: (0,size-1))
153     }
154         -- XXX: should really store a "high water mark" for dumping out
155         -- the binary data to a file.
156
157   | BinIO {             -- binary data stored in a file
158      bh_usr :: UserData,
159      off_r :: !FastMutInt,              -- the current offset (cached)
160      hdl   :: !IO.Handle                -- the file handle (must be seekable)
161    }
162         -- cache the file ptr in BinIO; using hTell is too expensive
163         -- to call repeatedly.  If anyone else is modifying this Handle
164         -- at the same time, we'll be screwed.
165
166 getUserData :: BinHandle -> UserData
167 getUserData bh = bh_usr bh
168
169 setUserData :: BinHandle -> UserData -> BinHandle
170 setUserData bh us = bh { bh_usr = us }
171
172
173 ---------------------------------------------------------------
174 --              Bin
175 ---------------------------------------------------------------
176
177 newtype Bin a = BinPtr Int 
178   deriving (Eq, Ord, Show, Bounded)
179
180 castBin :: Bin a -> Bin b
181 castBin (BinPtr i) = BinPtr i
182
183 ---------------------------------------------------------------
184 --              class Binary
185 ---------------------------------------------------------------
186
187 class Binary a where
188     put_   :: BinHandle -> a -> IO ()
189     put    :: BinHandle -> a -> IO (Bin a)
190     get    :: BinHandle -> IO a
191
192     -- define one of put_, put.  Use of put_ is recommended because it
193     -- is more likely that tail-calls can kick in, and we rarely need the
194     -- position return value.
195     put_ bh a = do put bh a; return ()
196     put bh a  = do p <- tellBin bh; put_ bh a; return p
197
198 putAt  :: Binary a => BinHandle -> Bin a -> a -> IO ()
199 putAt bh p x = do seekBin bh p; put bh x; return ()
200
201 getAt  :: Binary a => BinHandle -> Bin a -> IO a
202 getAt bh p = do seekBin bh p; get bh
203
204 openBinIO_ :: IO.Handle -> IO BinHandle
205 openBinIO_ h = openBinIO h 
206
207 openBinIO :: IO.Handle -> IO BinHandle
208 openBinIO h = do
209   r <- newFastMutInt
210   writeFastMutInt r 0
211   return (BinIO noUserData r h)
212
213 openBinMem :: Int -> IO BinHandle
214 openBinMem size
215  | size <= 0 = error "Data.Binary.openBinMem: size must be >= 0"
216  | otherwise = do
217    arr <- newArray_ (0,size-1)
218    arr_r <- newIORef arr
219    ix_r <- newFastMutInt
220    writeFastMutInt ix_r 0
221    sz_r <- newFastMutInt
222    writeFastMutInt sz_r size
223    return (BinMem noUserData ix_r sz_r arr_r)
224
225 tellBin :: BinHandle -> IO (Bin a)
226 tellBin (BinIO  _ r _)   = do ix <- readFastMutInt r; return (BinPtr ix)
227 tellBin (BinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix)
228
229 seekBin :: BinHandle -> Bin a -> IO ()
230 seekBin (BinIO _ ix_r h) (BinPtr p) = do 
231   writeFastMutInt ix_r p
232   hSeek h AbsoluteSeek (fromIntegral p)
233 seekBin h@(BinMem _ ix_r sz_r a) (BinPtr p) = do
234   sz <- readFastMutInt sz_r
235   if (p >= sz)
236         then do expandBin h p; writeFastMutInt ix_r p
237         else writeFastMutInt ix_r p
238
239 isEOFBin :: BinHandle -> IO Bool
240 isEOFBin (BinMem _ ix_r sz_r a) = do
241   ix <- readFastMutInt ix_r
242   sz <- readFastMutInt sz_r
243   return (ix >= sz)
244 isEOFBin (BinIO _ ix_r h) = hIsEOF h
245
246 writeBinMem :: BinHandle -> FilePath -> IO ()
247 writeBinMem (BinIO _ _ _) _ = error "Data.Binary.writeBinMem: not a memory handle"
248 writeBinMem (BinMem _ ix_r sz_r arr_r) fn = do
249   h <- openBinaryFile fn WriteMode
250   arr <- readIORef arr_r
251   ix  <- readFastMutInt ix_r
252   hPutArray h arr ix
253 #if __GLASGOW_HASKELL__ <= 500
254   -- workaround a bug in old implementation of hPutBuf (it doesn't
255   -- set the FILEOBJ_RW_WRITTEN flag on the file object, so the file doens't
256   -- get flushed properly).  Adding an extra '\0' doens't do any harm.
257   hPutChar h '\0'
258 #endif
259   hClose h
260
261 readBinMem :: FilePath -> IO BinHandle
262 -- Return a BinHandle with a totally undefined State
263 readBinMem filename = do
264   h <- openBinaryFile filename ReadMode
265   filesize' <- hFileSize h
266   let filesize = fromIntegral filesize'
267   arr <- newArray_ (0,filesize-1)
268   count <- hGetArray h arr filesize
269   when (count /= filesize)
270         (error ("Binary.readBinMem: only read " ++ show count ++ " bytes"))
271   hClose h
272   arr_r <- newIORef arr
273   ix_r <- newFastMutInt
274   writeFastMutInt ix_r 0
275   sz_r <- newFastMutInt
276   writeFastMutInt sz_r filesize
277   return (BinMem noUserData ix_r sz_r arr_r)
278
279 -- expand the size of the array to include a specified offset
280 expandBin :: BinHandle -> Int -> IO ()
281 expandBin (BinMem _ ix_r sz_r arr_r) off = do
282    sz <- readFastMutInt sz_r
283    let sz' = head (dropWhile (<= off) (iterate (* 2) sz))
284    arr <- readIORef arr_r
285    arr' <- newArray_ (0,sz'-1)
286    sequence_ [ unsafeRead arr i >>= unsafeWrite arr' i
287              | i <- [ 0 .. sz-1 ] ]
288    writeFastMutInt sz_r sz'
289    writeIORef arr_r arr'
290 #ifdef DEBUG
291    hPutStrLn stderr ("Binary: expanding to size: " ++ show sz')
292 #endif
293    return ()
294 expandBin (BinIO _ _ _) _ = return ()
295         -- no need to expand a file, we'll assume they expand by themselves.
296
297 -- -----------------------------------------------------------------------------
298 -- Low-level reading/writing of bytes
299
300 putWord8 :: BinHandle -> Word8 -> IO ()
301 putWord8 h@(BinMem _ ix_r sz_r arr_r) w = do
302     ix <- readFastMutInt ix_r
303     sz <- readFastMutInt sz_r
304         -- double the size of the array if it overflows
305     if (ix >= sz) 
306         then do expandBin h ix
307                 putWord8 h w
308         else do arr <- readIORef arr_r
309                 unsafeWrite arr ix w
310                 writeFastMutInt ix_r (ix+1)
311                 return ()
312 putWord8 (BinIO _ ix_r h) w = do
313     ix <- readFastMutInt ix_r
314     hPutChar h (chr (fromIntegral w))   -- XXX not really correct
315     writeFastMutInt ix_r (ix+1)
316     return ()
317
318 getWord8 :: BinHandle -> IO Word8
319 getWord8 (BinMem _ ix_r sz_r arr_r) = do
320     ix <- readFastMutInt ix_r
321     sz <- readFastMutInt sz_r
322     when (ix >= sz)  $
323 #if __GLASGOW_HASKELL__ <= 408
324         throw (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
325 #else
326         ioError (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
327 #endif
328     arr <- readIORef arr_r
329     w <- unsafeRead arr ix
330     writeFastMutInt ix_r (ix+1)
331     return w
332 getWord8 (BinIO _ ix_r h) = do
333     ix <- readFastMutInt ix_r
334     c <- hGetChar h
335     writeFastMutInt ix_r (ix+1)
336     return $! (fromIntegral (ord c))    -- XXX not really correct
337
338 putByte :: BinHandle -> Word8 -> IO ()
339 putByte bh w = put_ bh w
340
341 getByte :: BinHandle -> IO Word8
342 getByte = getWord8
343
344 -- -----------------------------------------------------------------------------
345 -- Primitve Word writes
346
347 instance Binary Word8 where
348   put_ = putWord8
349   get  = getWord8
350
351 instance Binary Word16 where
352   put_ h w = do -- XXX too slow.. inline putWord8?
353     putByte h (fromIntegral (w `shiftR` 8))
354     putByte h (fromIntegral (w .&. 0xff))
355   get h = do
356     w1 <- getWord8 h
357     w2 <- getWord8 h
358     return $! ((fromIntegral w1 `shiftL` 8) .|. fromIntegral w2)
359
360
361 instance Binary Word32 where
362   put_ h w = do
363     putByte h (fromIntegral (w `shiftR` 24))
364     putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
365     putByte h (fromIntegral ((w `shiftR` 8)  .&. 0xff))
366     putByte h (fromIntegral (w .&. 0xff))
367   get h = do
368     w1 <- getWord8 h
369     w2 <- getWord8 h
370     w3 <- getWord8 h
371     w4 <- getWord8 h
372     return $! ((fromIntegral w1 `shiftL` 24) .|. 
373                (fromIntegral w2 `shiftL` 16) .|. 
374                (fromIntegral w3 `shiftL`  8) .|. 
375                (fromIntegral w4))
376
377
378 instance Binary Word64 where
379   put_ h w = do
380     putByte h (fromIntegral (w `shiftR` 56))
381     putByte h (fromIntegral ((w `shiftR` 48) .&. 0xff))
382     putByte h (fromIntegral ((w `shiftR` 40) .&. 0xff))
383     putByte h (fromIntegral ((w `shiftR` 32) .&. 0xff))
384     putByte h (fromIntegral ((w `shiftR` 24) .&. 0xff))
385     putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff))
386     putByte h (fromIntegral ((w `shiftR`  8) .&. 0xff))
387     putByte h (fromIntegral (w .&. 0xff))
388   get h = do
389     w1 <- getWord8 h
390     w2 <- getWord8 h
391     w3 <- getWord8 h
392     w4 <- getWord8 h
393     w5 <- getWord8 h
394     w6 <- getWord8 h
395     w7 <- getWord8 h
396     w8 <- getWord8 h
397     return $! ((fromIntegral w1 `shiftL` 56) .|. 
398                (fromIntegral w2 `shiftL` 48) .|. 
399                (fromIntegral w3 `shiftL` 40) .|. 
400                (fromIntegral w4 `shiftL` 32) .|. 
401                (fromIntegral w5 `shiftL` 24) .|. 
402                (fromIntegral w6 `shiftL` 16) .|. 
403                (fromIntegral w7 `shiftL`  8) .|. 
404                (fromIntegral w8))
405
406 -- -----------------------------------------------------------------------------
407 -- Primitve Int writes
408
409 instance Binary Int8 where
410   put_ h w = put_ h (fromIntegral w :: Word8)
411   get h    = do w <- get h; return $! (fromIntegral (w::Word8))
412
413 instance Binary Int16 where
414   put_ h w = put_ h (fromIntegral w :: Word16)
415   get h    = do w <- get h; return $! (fromIntegral (w::Word16))
416
417 instance Binary Int32 where
418   put_ h w = put_ h (fromIntegral w :: Word32)
419   get h    = do w <- get h; return $! (fromIntegral (w::Word32))
420
421 instance Binary Int64 where
422   put_ h w = put_ h (fromIntegral w :: Word64)
423   get h    = do w <- get h; return $! (fromIntegral (w::Word64))
424
425 -- -----------------------------------------------------------------------------
426 -- Instances for standard types
427
428 instance Binary () where
429     put_ bh () = return ()
430     get  _     = return ()
431 --    getF bh p  = case getBitsF bh 0 p of (_,b) -> ((),b)
432
433 instance Binary Bool where
434     put_ bh b = putByte bh (fromIntegral (fromEnum b))
435     get  bh   = do x <- getWord8 bh; return $! (toEnum (fromIntegral x))
436 --    getF bh p = case getBitsF bh 1 p of (x,b) -> (toEnum x,b)
437
438 instance Binary Char where
439     put_  bh c = put_ bh (fromIntegral (ord c) :: Word32)
440     get  bh   = do x <- get bh; return $! (chr (fromIntegral (x :: Word32)))
441 --    getF bh p = case getBitsF bh 8 p of (x,b) -> (toEnum x,b)
442
443 instance Binary Int where
444 #if SIZEOF_HSINT == 4
445     put_ bh i = put_ bh (fromIntegral i :: Int32)
446     get  bh = do
447         x <- get bh
448         return $! (fromIntegral (x :: Int32))
449 #elif SIZEOF_HSINT == 8
450     put_ bh i = put_ bh (fromIntegral i :: Int64)
451     get  bh = do
452         x <- get bh
453         return $! (fromIntegral (x :: Int64))
454 #else
455 #error "unsupported sizeof(HsInt)"
456 #endif
457 --    getF bh   = getBitsF bh 32
458
459 instance Binary a => Binary [a] where
460     put_ bh []     = putByte bh 0
461     put_ bh (x:xs) = do putByte bh 1; put_ bh x; put_ bh xs
462     get bh         = do h <- getWord8 bh
463                         case h of
464                           0 -> return []
465                           _ -> do x  <- get bh
466                                   xs <- get bh
467                                   return (x:xs)
468
469 instance (Binary a, Binary b) => Binary (a,b) where
470     put_ bh (a,b) = do put_ bh a; put_ bh b
471     get bh        = do a <- get bh
472                        b <- get bh
473                        return (a,b)
474
475 instance (Binary a, Binary b, Binary c) => Binary (a,b,c) where
476     put_ bh (a,b,c) = do put_ bh a; put_ bh b; put_ bh c
477     get bh          = do a <- get bh
478                          b <- get bh
479                          c <- get bh
480                          return (a,b,c)
481
482 instance (Binary a, Binary b, Binary c, Binary d) => Binary (a,b,c,d) where
483     put_ bh (a,b,c,d) = do put_ bh a; put_ bh b; put_ bh c; put_ bh d
484     get bh          = do a <- get bh
485                          b <- get bh
486                          c <- get bh
487                          d <- get bh
488                          return (a,b,c,d)
489
490 instance Binary a => Binary (Maybe a) where
491     put_ bh Nothing  = putByte bh 0
492     put_ bh (Just a) = do putByte bh 1; put_ bh a
493     get bh           = do h <- getWord8 bh
494                           case h of
495                             0 -> return Nothing
496                             _ -> do x <- get bh; return (Just x)
497
498 instance (Binary a, Binary b) => Binary (Either a b) where
499     put_ bh (Left  a) = do putByte bh 0; put_ bh a
500     put_ bh (Right b) = do putByte bh 1; put_ bh b
501     get bh            = do h <- getWord8 bh
502                            case h of
503                              0 -> do a <- get bh ; return (Left a)
504                              _ -> do b <- get bh ; return (Right b)
505
506 #ifdef __GLASGOW_HASKELL__
507 instance Binary Integer where
508     put_ bh (S# i#) = do putByte bh 0; put_ bh (I# i#)
509     put_ bh (J# s# a#) = do
510         p <- putByte bh 1;
511         put_ bh (I# s#)
512         let sz# = sizeofByteArray# a#  -- in *bytes*
513         put_ bh (I# sz#)  -- in *bytes*
514         putByteArray bh a# sz#
515    
516     get bh = do 
517         b <- getByte bh
518         case b of
519           0 -> do (I# i#) <- get bh
520                   return (S# i#)
521           _ -> do (I# s#) <- get bh
522                   sz <- get bh
523                   (BA a#) <- getByteArray bh sz
524                   return (J# s# a#)
525
526 putByteArray :: BinHandle -> ByteArray# -> Int# -> IO ()
527 putByteArray bh a s# = loop 0#
528   where loop n# 
529            | n# ==# s# = return ()
530            | otherwise = do
531                 putByte bh (indexByteArray a n#)
532                 loop (n# +# 1#)
533
534 getByteArray :: BinHandle -> Int -> IO ByteArray
535 getByteArray bh (I# sz) = do
536   (MBA arr) <- newByteArray sz 
537   let loop n
538            | n ==# sz = return ()
539            | otherwise = do
540                 w <- getByte bh 
541                 writeByteArray arr n w
542                 loop (n +# 1#)
543   loop 0#
544   freezeByteArray arr
545
546
547 data ByteArray = BA ByteArray#
548 data MBA = MBA (MutableByteArray# RealWorld)
549
550 newByteArray :: Int# -> IO MBA
551 newByteArray sz = IO $ \s ->
552   case newByteArray# sz s of { (# s, arr #) ->
553   (# s, MBA arr #) }
554
555 freezeByteArray :: MutableByteArray# RealWorld -> IO ByteArray
556 freezeByteArray arr = IO $ \s ->
557   case unsafeFreezeByteArray# arr s of { (# s, arr #) ->
558   (# s, BA arr #) }
559
560 writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO ()
561
562 #if __GLASGOW_HASKELL__ < 503
563 writeByteArray arr i w8 = IO $ \s ->
564   case word8ToWord w8 of { W# w# -> 
565   case writeCharArray# arr i (chr# (word2Int# w#)) s  of { s ->
566   (# s , () #) }}
567 #else
568 writeByteArray arr i (W8# w) = IO $ \s ->
569   case writeWord8Array# arr i w s of { s ->
570   (# s, () #) }
571 #endif
572
573 #if __GLASGOW_HASKELL__ < 503
574 indexByteArray a# n# = fromIntegral (I# (ord# (indexCharArray# a# n#)))
575 #else
576 indexByteArray a# n# = W8# (indexWord8Array# a# n#)
577 #endif
578
579 instance (Integral a, Binary a) => Binary (Ratio a) where
580     put_ bh (a :% b) = do put_ bh a; put_ bh b
581     get bh = do a <- get bh; b <- get bh; return (a :% b)
582 #endif
583
584 instance Binary (Bin a) where
585   put_ bh (BinPtr i) = put_ bh i
586   get bh = do i <- get bh; return (BinPtr i)
587
588 -- -----------------------------------------------------------------------------
589 -- Lazy reading/writing
590
591 lazyPut :: Binary a => BinHandle -> a -> IO ()
592 lazyPut bh a = do
593         -- output the obj with a ptr to skip over it:
594     pre_a <- tellBin bh
595     put_ bh pre_a       -- save a slot for the ptr
596     put_ bh a           -- dump the object
597     q <- tellBin bh     -- q = ptr to after object
598     putAt bh pre_a q    -- fill in slot before a with ptr to q
599     seekBin bh q        -- finally carry on writing at q
600
601 lazyGet :: Binary a => BinHandle -> IO a
602 lazyGet bh = do
603     p <- get bh         -- a BinPtr
604     p_a <- tellBin bh
605     a <- unsafeInterleaveIO (getAt bh p_a)
606     seekBin bh p -- skip over the object for now
607     return a
608
609 -- --------------------------------------------------------------
610 --      Main wrappers: getBinFileWithDict, putBinFileWithDict
611 --
612 --      This layer is built on top of the stuff above, 
613 --      and should not know anything about BinHandles
614 -- --------------------------------------------------------------
615
616 initBinMemSize       = (1024*1024) :: Int
617 binaryInterfaceMagic = 0x1face :: Word32
618
619 getBinFileWithDict :: Binary a => FilePath -> IO a
620 getBinFileWithDict file_path = do
621   bh <- Binary.readBinMem file_path
622
623         -- Read the magic number to check that this really is a GHC .hi file
624         -- (This magic number does not change when we change 
625         --  GHC interface file format)
626   magic <- get bh
627   when (magic /= binaryInterfaceMagic) $
628         throwDyn (ProgramError (
629            "magic number mismatch: old/corrupt interface file?"))
630
631         -- Read the dictionary
632         -- The next word in the file is a pointer to where the dictionary is
633         -- (probably at the end of the file)
634   dict_p <- Binary.get bh       -- Get the dictionary ptr
635   data_p <- tellBin bh          -- Remember where we are now
636   seekBin bh dict_p
637   dict <- getDictionary bh
638   seekBin bh data_p             -- Back to where we were before
639
640         -- Initialise the user-data field of bh
641   let bh' = setUserData bh (initReadState dict)
642         
643         -- At last, get the thing 
644   get bh'
645
646 putBinFileWithDict :: Binary a => FilePath -> a -> IO ()
647 putBinFileWithDict file_path the_thing = do
648   bh <- openBinMem initBinMemSize
649   put_ bh binaryInterfaceMagic
650
651         -- Remember where the dictionary pointer will go
652   dict_p_p <- tellBin bh
653   put_ bh dict_p_p      -- Placeholder for ptr to dictionary
654
655         -- Make some intial state
656   usr_state <- newWriteState
657
658         -- Put the main thing, 
659   put_ (setUserData bh usr_state) the_thing
660
661         -- Get the final-state
662   j <- readIORef  (ud_next usr_state)
663   fm <- readIORef (ud_map  usr_state)
664   dict_p <- tellBin bh  -- This is where the dictionary will start
665
666         -- Write the dictionary pointer at the fornt of the file
667   putAt bh dict_p_p dict_p      -- Fill in the placeholder
668   seekBin bh dict_p             -- Seek back to the end of the file
669
670         -- Write the dictionary itself
671   putDictionary bh j (constructDictionary j fm)
672
673         -- And send the result to the file
674   writeBinMem bh file_path
675   
676 -- -----------------------------------------------------------------------------
677 -- UserData
678 -- -----------------------------------------------------------------------------
679
680 data UserData = 
681    UserData {   -- This field is used only when reading
682               ud_dict :: Dictionary,
683
684                 -- The next two fields are only used when writing
685               ud_next :: IORef Int,     -- The next index to use
686               ud_map  :: IORef (UniqFM (Int,FastString))
687         }
688
689 noUserData = error "Binary.UserData: no user data"
690
691 initReadState :: Dictionary -> UserData
692 initReadState dict = UserData{ ud_dict = dict,
693                                ud_next = undef "next",
694                                ud_map  = undef "map" }
695
696 newWriteState :: IO UserData
697 newWriteState = do
698   j_r <- newIORef 0
699   out_r <- newIORef emptyUFM
700   return (UserData { ud_dict = panic "dict",
701                      ud_next = j_r,
702                      ud_map  = out_r })
703
704
705 undef s = panic ("Binary.UserData: no " ++ s)
706
707 ---------------------------------------------------------
708 --              The Dictionary 
709 ---------------------------------------------------------
710
711 type Dictionary = Array Int FastString  -- The dictionary
712                                         -- Should be 0-indexed
713
714 putDictionary :: BinHandle -> Int -> Dictionary -> IO ()
715 putDictionary bh sz dict = do
716   put_ bh sz
717   mapM_ (putFS bh) (elems dict)
718
719 getDictionary :: BinHandle -> IO Dictionary
720 getDictionary bh = do 
721   sz <- get bh
722   elems <- sequence (take sz (repeat (getFS bh)))
723   return (listArray (0,sz-1) elems)
724
725 constructDictionary :: Int -> UniqFM (Int,FastString) -> Dictionary
726 constructDictionary j fm = array (0,j-1) (eltsUFM fm)
727
728 ---------------------------------------------------------
729 --              Reading and writing FastStrings
730 ---------------------------------------------------------
731
732 putFS bh (FastString id l ba) = do
733   put_ bh (I# l)
734   putByteArray bh ba l
735 putFS bh s = error ("Binary.put_(FastString): " ++ unpackFS s)
736         -- Note: the length of the FastString is *not* the same as
737         -- the size of the ByteArray: the latter is rounded up to a
738         -- multiple of the word size.
739   
740 {- -- possible faster version, not quite there yet:
741 getFS bh@BinMem{} = do
742   (I# l) <- get bh
743   arr <- readIORef (arr_r bh)
744   off <- readFastMutInt (off_r bh)
745   return $! (mkFastSubStringBA# arr off l)
746 -}
747 getFS bh = do
748   (I# l) <- get bh
749   (BA ba) <- getByteArray bh (I# l)
750   return $! (mkFastSubStringBA# ba 0# l)
751
752 instance Binary FastString where
753   put_ bh f@(FastString id l ba) =
754     case getUserData bh of { 
755         UserData { ud_next = j_r, ud_map = out_r, ud_dict = dict} -> do
756     out <- readIORef out_r
757     let uniq = getUnique f
758     case lookupUFM out uniq of
759         Just (j,f)  -> put_ bh j
760         Nothing -> do
761            j <- readIORef j_r
762            put_ bh j
763            writeIORef j_r (j+1)
764            writeIORef out_r (addToUFM out uniq (j,f))
765     }
766   put_ bh s = error ("Binary.put_(FastString): " ++ show (unpackFS s))
767
768   get bh = do 
769         j <- get bh
770         return $! (ud_dict (getUserData bh) ! j)