Safe Haskell | None |
---|---|
Language | GHC2021 |
Binary interface file support.
Synopsis
- writeBinIface :: Profile -> TraceBinIFace -> CompressionIFace -> FilePath -> ModIface -> IO ()
- readBinIface :: Profile -> NameCache -> CheckHiWay -> TraceBinIFace -> FilePath -> IO ModIface
- readBinIfaceHeader :: Profile -> NameCache -> CheckHiWay -> TraceBinIFace -> FilePath -> IO (Fingerprint, ReadBinHandle)
- data CompressionIFace
- getSymtabName :: SymbolTable Name -> ReadBinHandle -> IO Name
- data CheckHiWay
- data TraceBinIFace
- = TraceBinIFace (SDoc -> IO ())
- | QuietBinIFace
- getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface
- putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO ()
- getWithUserData :: Binary a => NameCache -> ReadBinHandle -> IO a
- putWithUserData :: Binary a => TraceBinIFace -> CompressionIFace -> WriteBinHandle -> a -> IO ()
- getSymbolTable :: ReadBinHandle -> NameCache -> IO (SymbolTable Name)
- putName :: BinSymbolTable -> WriteBinHandle -> Name -> IO ()
- putSymbolTable :: WriteBinHandle -> Int -> UniqFM Name (Int, Name) -> IO ()
- data BinSymbolTable = BinSymbolTable {
- bin_symtab_next :: !FastMutInt
- bin_symtab_map :: !(IORef (UniqFM Name (Int, Name)))
- initWriteIfaceType :: CompressionIFace -> IO (WriterTable, BinaryWriter IfaceType)
- initReadIfaceTypeTable :: ReaderUserData -> IO (ReaderTable IfaceType)
- putAllTables :: WriteBinHandle -> [WriterTable] -> IO b -> IO ([Int], b)
Public API for interface file serialisation
writeBinIface :: Profile -> TraceBinIFace -> CompressionIFace -> FilePath -> ModIface -> IO () Source #
Write an interface file.
See Note [Deduplication during iface binary serialisation] for details.
readBinIface :: Profile -> NameCache -> CheckHiWay -> TraceBinIFace -> FilePath -> IO ModIface Source #
Read an interface file.
See Note [Deduplication during iface binary serialisation] for details.
readBinIfaceHeader :: Profile -> NameCache -> CheckHiWay -> TraceBinIFace -> FilePath -> IO (Fingerprint, ReadBinHandle) Source #
Read an interface file header, checking the magic number, version, and way. Returns the hash of the source file and a BinHandle which points at the start of the rest of the interface file data.
data CompressionIFace Source #
The compression/deduplication level of ModIface
files.
A ModIface
contains many duplicated symbols and names. To keep interface
files small, we deduplicate them during serialisation.
It is impossible to write an interface file with *no* compression/deduplication.
We support different levels of compression/deduplication, with different
trade-offs for run-time performance and memory usage.
If you don't have any specific requirements, then SafeExtraCompression
is a good default.
NormalCompression | Perform the normal compression operations,
such as deduplicating |
SafeExtraCompression | Perform some extra compression steps that have minimal impact
on the run-time of This reduces the size of '.hi' files significantly in some cases and reduces overall memory usage in certain scenarios. |
MaximumCompression | Try to compress as much as possible. Yields the smallest '.hi' files but at the cost of additional run-time. |
Instances
getSymtabName :: SymbolTable Name -> ReadBinHandle -> IO Name Source #
data CheckHiWay Source #
Instances
Eq CheckHiWay Source # | |
Defined in GHC.Iface.Binary (==) :: CheckHiWay -> CheckHiWay -> Bool # (/=) :: CheckHiWay -> CheckHiWay -> Bool # |
data TraceBinIFace Source #
TraceBinIFace (SDoc -> IO ()) | |
QuietBinIFace |
getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface Source #
putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () Source #
Puts the ModIface
to the WriteBinHandle
.
This avoids serialisation of the ModIface
if the fields mi_hi_bytes
contains a
Just
value. This field is populated by reading the ModIface
using
getIfaceWithExtFields
and not modifying it in any way afterwards.
getWithUserData :: Binary a => NameCache -> ReadBinHandle -> IO a Source #
This performs a get action after reading the dictionary and symbol table. It is necessary to run this before trying to deserialise any Names or FastStrings.
putWithUserData :: Binary a => TraceBinIFace -> CompressionIFace -> WriteBinHandle -> a -> IO () Source #
Put a piece of data with an initialised UserData
field. This
is necessary if you want to serialise Names or FastStrings.
It also writes a symbol table and the dictionary.
This segment should be read using getWithUserData
.
Internal serialisation functions
getSymbolTable :: ReadBinHandle -> NameCache -> IO (SymbolTable Name) Source #
putName :: BinSymbolTable -> WriteBinHandle -> Name -> IO () Source #
putSymbolTable :: WriteBinHandle -> Int -> UniqFM Name (Int, Name) -> IO () Source #
data BinSymbolTable Source #
BinSymbolTable | |
|
putAllTables :: WriteBinHandle -> [WriterTable] -> IO b -> IO ([Int], b) Source #
Write all deduplication tables to disk after serialising the main payload.
Writes forward pointers to the deduplication tables before writing the payload to allow deserialisation *before* the payload is read again.