Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Sylvain Henry <sylvain.henry@iohk.io> Jeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Josh Meredith <josh.meredith@iohk.io> |
Stability | experimental Serialization/deserialization of binary .o files for the JavaScript backend The .o files contain dependency information and generated code. All strings are mapped to a central string table, which helps reduce file size and gives us efficient hash consing on read Binary intermediate JavaScript object files: serialized [Text] -> ([ClosureInfo], JStat) blocks file layout: - magic "GHCJSOBJ" - compiler version tag - module name - offsets of string table - dependencies - offset of the index - unit infos - index - string table |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- putObject :: BinHandle -> ModuleName -> BlockInfo -> [ObjBlock] -> IO ()
- getObjectHeader :: BinHandle -> IO (Either String ModuleName)
- getObjectBody :: BinHandle -> ModuleName -> IO Object
- getObject :: BinHandle -> IO (Maybe Object)
- readObject :: FilePath -> IO (Maybe Object)
- getObjectBlocks :: Object -> BlockIds -> IO [ObjBlock]
- readObjectBlocks :: FilePath -> BlockIds -> IO [ObjBlock]
- readObjectBlockInfo :: FilePath -> IO (Maybe BlockInfo)
- isGlobalBlock :: BlockId -> Bool
- isJsObjectFile :: FilePath -> IO Bool
- data Object = Object {
- objModuleName :: !ModuleName
- objHandle :: !BinHandle
- objPayloadOffset :: !(Bin ObjBlock)
- objBlockInfo :: !BlockInfo
- objIndex :: !Index
- data IndexEntry = IndexEntry {
- idxSymbols :: ![FastString]
- idxOffset :: !(Bin ObjBlock)
- data LocatedBlockInfo = LocatedBlockInfo {
- lbi_loc :: !BlockLocation
- lbi_info :: !BlockInfo
- data BlockInfo = BlockInfo {
- bi_module :: !Module
- bi_must_link :: !BlockIds
- bi_exports :: !(Map ExportedFun BlockId)
- bi_block_deps :: !(Array BlockId BlockDeps)
- data BlockDeps = BlockDeps {
- blockBlockDeps :: [BlockId]
- blockFunDeps :: [ExportedFun]
- data BlockLocation
- type BlockId = Int
- type BlockIds = IntSet
- data BlockRef = BlockRef {
- block_ref_mod :: !Module
- block_ref_idx :: !BlockId
- data ExportedFun = ExportedFun {}
Documentation
:: BinHandle | |
-> ModuleName | module |
-> BlockInfo | block infos |
-> [ObjBlock] | linkable units and their symbols |
-> IO () |
Given a handle to a Binary payload, add the module, mod_name
, its
dependencies, deps
, and its linkable units to the payload.
getObjectHeader :: BinHandle -> IO (Either String ModuleName) Source #
Parse object header
getObjectBody :: BinHandle -> ModuleName -> IO Object Source #
Parse object body. Must be called after a sucessful getObjectHeader
readObject :: FilePath -> IO (Maybe Object) Source #
Read object from file
The object is still in memory after this (see objHandle).
getObjectBlocks :: Object -> BlockIds -> IO [ObjBlock] Source #
Get blocks in the object file, using the given filtering function
readObjectBlocks :: FilePath -> BlockIds -> IO [ObjBlock] Source #
Read blocks in the object file, using the given filtering function
readObjectBlockInfo :: FilePath -> IO (Maybe BlockInfo) Source #
Reads only the part necessary to get the block info
isGlobalBlock :: BlockId -> Bool Source #
we use the convention that the first block (0) is a module-global block that's always included when something from the module is loaded. everything in a module implicitly depends on the global block. The global block itself can't have dependencies
An object file
Object | |
|
data IndexEntry Source #
IndexEntry | |
|
Instances
Binary IndexEntry Source # | |
Defined in GHC.StgToJS.Object put_ :: BinHandle -> IndexEntry -> IO () Source # put :: BinHandle -> IndexEntry -> IO (Bin IndexEntry) Source # |
data LocatedBlockInfo Source #
LocatedBlockInfo | |
|
Information about blocks (linkable units)
BlockInfo | |
|
Instances
BlockDeps | |
|
data BlockLocation Source #
Where are the blocks
ObjectFile FilePath | In an object file at path |
ArchiveFile FilePath | In a Ar file at path |
InMemory String Object | In memory |
Instances
Outputable BlockLocation Source # | |
Defined in GHC.StgToJS.Object ppr :: BlockLocation -> SDoc Source # |
A BlockRef
is a pair of a module and the index of the block in the
object file
BlockRef | |
|
data ExportedFun Source #
Exported Functions
ExportedFun | |
|
Instances
Binary ExportedFun Source # | |
Defined in GHC.StgToJS.Object put_ :: BinHandle -> ExportedFun -> IO () Source # put :: BinHandle -> ExportedFun -> IO (Bin ExportedFun) Source # | |
Outputable ExportedFun Source # | |
Defined in GHC.StgToJS.Object ppr :: ExportedFun -> SDoc Source # | |
Eq ExportedFun Source # | |
Defined in GHC.StgToJS.Object (==) :: ExportedFun -> ExportedFun -> Bool # (/=) :: ExportedFun -> ExportedFun -> Bool # | |
Ord ExportedFun Source # | |
Defined in GHC.StgToJS.Object compare :: ExportedFun -> ExportedFun -> Ordering # (<) :: ExportedFun -> ExportedFun -> Bool # (<=) :: ExportedFun -> ExportedFun -> Bool # (>) :: ExportedFun -> ExportedFun -> Bool # (>=) :: ExportedFun -> ExportedFun -> Bool # max :: ExportedFun -> ExportedFun -> ExportedFun # min :: ExportedFun -> ExportedFun -> ExportedFun # |
Orphan instances
Binary AOp Source # | |
Binary JExpr Source # | |
Binary JStat Source # | |
Binary JVal Source # | |
Binary Op Source # | |
Binary UOp Source # | |
Binary Ident Source # | |
Binary CILayout Source # | |
Binary CIRegs Source # | |
Binary CIStatic Source # | |
Binary CIType Source # | |
Binary ClosureInfo Source # | |
put_ :: BinHandle -> ClosureInfo -> IO () Source # put :: BinHandle -> ClosureInfo -> IO (Bin ClosureInfo) Source # | |
Binary ExpFun Source # | |
Binary ForeignJSRef Source # | |
put_ :: BinHandle -> ForeignJSRef -> IO () Source # put :: BinHandle -> ForeignJSRef -> IO (Bin ForeignJSRef) Source # | |
Binary JSFFIType Source # | |
Binary StaticArg Source # | |
Binary StaticInfo Source # | |
put_ :: BinHandle -> StaticInfo -> IO () Source # put :: BinHandle -> StaticInfo -> IO (Bin StaticInfo) Source # | |
Binary StaticLit Source # | |
Binary StaticUnboxed Source # | |
put_ :: BinHandle -> StaticUnboxed -> IO () Source # put :: BinHandle -> StaticUnboxed -> IO (Bin StaticUnboxed) Source # | |
Binary StaticVal Source # | |
Binary VarType Source # | |