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 |
Safe Haskell | None |
Language | GHC2021 |
Synopsis
- data ObjectKind
- getObjectKind :: FilePath -> IO (Maybe ObjectKind)
- getObjectKindBS :: ByteString -> Maybe ObjectKind
- data JSOptions = JSOptions {
- enableCPP :: !Bool
- emccExtraOptions :: ![String]
- emccExportedFunctions :: ![String]
- emccExportedRuntimeMethods :: ![String]
- defaultJSOptions :: JSOptions
- getOptionsFromJsFile :: FilePath -> IO JSOptions
- writeJSObject :: JSOptions -> ByteString -> FilePath -> IO ()
- readJSObject :: FilePath -> IO (JSOptions, ByteString)
- parseJSObject :: ReadBinHandle -> IO (JSOptions, ByteString)
- parseJSObjectBS :: ByteString -> IO (JSOptions, ByteString)
- putObject :: WriteBinHandle -> ModuleName -> BlockInfo -> [ObjBlock] -> IO ()
- getObjectHeader :: ReadBinHandle -> IO (Either String ModuleName)
- getObjectBody :: ReadBinHandle -> ModuleName -> IO Object
- getObject :: ReadBinHandle -> 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
- data Object = Object {
- objModuleName :: !ModuleName
- objHandle :: !ReadBinHandle
- 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
data ObjectKind Source #
Different kinds of object (.o) supported by the JS backend
ObjJs | JavaScript source embedded in a .o |
ObjHs | JS backend object for Haskell code |
ObjCc | Wasm module object as produced by emcc |
Instances
Show ObjectKind Source # | |
Defined in GHC.StgToJS.Object showsPrec :: Int -> ObjectKind -> ShowS # show :: ObjectKind -> String # showList :: [ObjectKind] -> ShowS # | |
Eq ObjectKind Source # | |
Defined in GHC.StgToJS.Object (==) :: ObjectKind -> ObjectKind -> Bool # (/=) :: ObjectKind -> ObjectKind -> Bool # | |
Ord ObjectKind Source # | |
Defined in GHC.StgToJS.Object compare :: ObjectKind -> ObjectKind -> Ordering # (<) :: ObjectKind -> ObjectKind -> Bool # (<=) :: ObjectKind -> ObjectKind -> Bool # (>) :: ObjectKind -> ObjectKind -> Bool # (>=) :: ObjectKind -> ObjectKind -> Bool # max :: ObjectKind -> ObjectKind -> ObjectKind # min :: ObjectKind -> ObjectKind -> ObjectKind # |
getObjectKind :: FilePath -> IO (Maybe ObjectKind) Source #
Get the kind of a file object, if any
getObjectKindBS :: ByteString -> Maybe ObjectKind Source #
Get the kind of an object stored in a bytestring, if any
JS object
Options obtained from pragmas in JS files
JSOptions | |
|
Parse option pragma in JS file
writeJSObject :: JSOptions -> ByteString -> FilePath -> IO () Source #
Write a JS object (embed some handwritten JS code)
readJSObject :: FilePath -> IO (JSOptions, ByteString) Source #
Read a JS object from file
parseJSObject :: ReadBinHandle -> IO (JSOptions, ByteString) Source #
Read a JS object from BinHandle
parseJSObjectBS :: ByteString -> IO (JSOptions, ByteString) Source #
Read a JS object from ByteString
HS object
:: WriteBinHandle | |
-> 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 :: ReadBinHandle -> IO (Either String ModuleName) Source #
Parse object header
getObjectBody :: ReadBinHandle -> ModuleName -> IO Object Source #
Parse object body. Must be called after a successful 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
A HS object file
Object | |
|
data IndexEntry Source #
IndexEntry | |
|
Instances
Binary IndexEntry Source # | |
Defined in GHC.StgToJS.Object put_ :: WriteBinHandle -> IndexEntry -> IO () Source # put :: WriteBinHandle -> IndexEntry -> IO (Bin IndexEntry) Source # get :: ReadBinHandle -> IO IndexEntry Source # |
data LocatedBlockInfo Source #
LocatedBlockInfo | |
|
Information about blocks (linkable units)
BlockInfo | |
|
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_ :: WriteBinHandle -> ExportedFun -> IO () Source # put :: WriteBinHandle -> ExportedFun -> IO (Bin ExportedFun) Source # get :: ReadBinHandle -> IO 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 # |