Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Binary interface file support.
Synopsis
- writeBinIface :: Profile -> TraceBinIFace -> FilePath -> ModIface -> IO ()
- readBinIface :: CheckHiWay -> TraceBinIFace -> FilePath -> TcRnIf a b ModIface
- readBinIface_ :: Profile -> CheckHiWay -> TraceBinIFace -> FilePath -> NameCacheUpdater -> IO ModIface
- getSymtabName :: NameCacheUpdater -> Dictionary -> SymbolTable -> BinHandle -> IO Name
- getDictFastString :: Dictionary -> BinHandle -> IO FastString
- data CheckHiWay
- data TraceBinIFace
- = TraceBinIFace (SDoc -> IO ())
- | QuietBinIFace
- getWithUserData :: Binary a => NameCacheUpdater -> BinHandle -> IO a
- putWithUserData :: Binary a => TraceBinIFace -> BinHandle -> a -> IO ()
- getSymbolTable :: BinHandle -> NameCacheUpdater -> IO SymbolTable
- putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
- putDictionary :: BinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO ()
- putFastString :: BinDictionary -> BinHandle -> FastString -> IO ()
- putSymbolTable :: BinHandle -> Int -> UniqFM Name (Int, Name) -> IO ()
- data BinSymbolTable = BinSymbolTable {
- bin_symtab_next :: !FastMutInt
- bin_symtab_map :: !(IORef (UniqFM Name (Int, Name)))
- data BinDictionary = BinDictionary {
- bin_dict_next :: !FastMutInt
- bin_dict_map :: !(IORef (UniqFM FastString (Int, FastString)))
Public API for interface file serialisation
writeBinIface :: Profile -> TraceBinIFace -> FilePath -> ModIface -> IO () Source #
Write an interface file
readBinIface :: CheckHiWay -> TraceBinIFace -> FilePath -> TcRnIf a b ModIface Source #
Read an interface file
readBinIface_ :: Profile -> CheckHiWay -> TraceBinIFace -> FilePath -> NameCacheUpdater -> IO ModIface Source #
Read an interface file in IO
.
getSymtabName :: NameCacheUpdater -> Dictionary -> SymbolTable -> BinHandle -> IO Name Source #
getDictFastString :: Dictionary -> BinHandle -> IO FastString 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 |
getWithUserData :: Binary a => NameCacheUpdater -> BinHandle -> 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 -> BinHandle -> 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 :: BinHandle -> NameCacheUpdater -> IO SymbolTable Source #
putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO () Source #
putDictionary :: BinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO () Source #
putFastString :: BinDictionary -> BinHandle -> FastString -> IO () Source #
data BinSymbolTable Source #
BinSymbolTable | |
|
data BinDictionary Source #
BinDictionary | |
|