| 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 | Safe-Inferred | 
| Language | Haskell2010 | 
GHC.StgToJS.Object
Contents
Description
Synopsis
- putObject :: BinHandle -> ModuleName -> Deps -> [ObjUnit] -> IO ()
- getObjectHeader :: BinHandle -> IO (Either String ModuleName)
- getObjectBody :: BinHandle -> ModuleName -> IO Object
- getObject :: BinHandle -> IO (Maybe Object)
- readObject :: FilePath -> IO (Maybe Object)
- getObjectUnits :: Object -> (Word -> IndexEntry -> Bool) -> IO [ObjUnit]
- readObjectUnits :: FilePath -> (Word -> IndexEntry -> Bool) -> IO [ObjUnit]
- readObjectDeps :: FilePath -> IO (Maybe Deps)
- isGlobalUnit :: Int -> Bool
- isJsObjectFile :: FilePath -> IO Bool
- data Object = Object {- objModuleName :: !ModuleName
- objHandle :: !BinHandle
- objPayloadOffset :: !(Bin ObjUnit)
- objDeps :: !Deps
- objIndex :: !Index
 
- data IndexEntry = IndexEntry {- idxSymbols :: ![FastString]
- idxOffset :: !(Bin ObjUnit)
 
- data Deps = Deps {- depsModule :: !Module
- depsRequired :: !BlockIds
- depsHaskellExported :: !(Map ExportedFun BlockId)
- depsBlocks :: !(Array BlockId BlockDeps)
 
- data BlockDeps = BlockDeps {- blockBlockDeps :: [Int]
- blockFunDeps :: [ExportedFun]
 
- data DepsLocation
- data ExportedFun = ExportedFun {}
Documentation
Arguments
| :: BinHandle | |
| -> ModuleName | module | 
| -> Deps | dependencies | 
| -> [ObjUnit] | 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).
getObjectUnits :: Object -> (Word -> IndexEntry -> Bool) -> IO [ObjUnit] Source #
Get units in the object file, using the given filtering function
readObjectUnits :: FilePath -> (Word -> IndexEntry -> Bool) -> IO [ObjUnit] Source #
Read units in the object file, using the given filtering function
readObjectDeps :: FilePath -> IO (Maybe Deps) Source #
Reads only the part necessary to get the dependencies
isGlobalUnit :: Int -> Bool Source #
we use the convention that the first unit (0) is a module-global unit that's always included when something from the module is loaded. everything in a module implicitly depends on the global block. the global unit itself can't have dependencies
An object file
Constructors
| Object | |
| Fields 
 | |
data IndexEntry Source #
Constructors
| IndexEntry | |
| Fields 
 | |
Instances
| Binary IndexEntry Source # | |
| Defined in GHC.StgToJS.Object Methods put_ :: BinHandle -> IndexEntry -> IO () Source # put :: BinHandle -> IndexEntry -> IO (Bin IndexEntry) Source # | |
dependencies for a single module
Constructors
| Deps | |
| Fields 
 | |
Constructors
| BlockDeps | |
| Fields 
 | |
data DepsLocation Source #
Where are the dependencies
Constructors
| ObjectFile FilePath | In an object file at path | 
| ArchiveFile FilePath | In a Ar file at path | 
| InMemory String Object | In memory | 
Instances
| Outputable DepsLocation Source # | |
| Defined in GHC.StgToJS.Object Methods ppr :: DepsLocation -> SDoc Source # | |
data ExportedFun Source #
Exported Functions
Constructors
| ExportedFun | |
| Fields 
 | |
Instances
| Binary ExportedFun Source # | |
| Defined in GHC.StgToJS.Object Methods put_ :: BinHandle -> ExportedFun -> IO () Source # put :: BinHandle -> ExportedFun -> IO (Bin ExportedFun) Source # | |
| Outputable ExportedFun Source # | |
| Defined in GHC.StgToJS.Object Methods ppr :: ExportedFun -> SDoc Source # | |
| Eq ExportedFun Source # | |
| Defined in GHC.StgToJS.Object | |
| Ord ExportedFun Source # | |
| Defined in GHC.StgToJS.Object Methods compare :: ExportedFun -> ExportedFun -> Ordering # (<) :: ExportedFun -> ExportedFun -> Bool # (<=) :: ExportedFun -> ExportedFun -> Bool # (>) :: ExportedFun -> ExportedFun -> Bool # (>=) :: ExportedFun -> ExportedFun -> Bool # max :: ExportedFun -> ExportedFun -> ExportedFun # min :: ExportedFun -> ExportedFun -> ExportedFun # | |