Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Jeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io> |
Stability | experimental |
Safe Haskell | None |
Language | GHC2021 |
GHCJS linker, collects dependencies from the object files which contain linkable units with dependency information
Synopsis
- jsLinkBinary :: FinderCache -> JSLinkConfig -> StgToJSConfig -> Logger -> TmpFs -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO ()
- jsLink :: JSLinkConfig -> StgToJSConfig -> Logger -> TmpFs -> ArchiveCache -> FilePath -> LinkPlan -> IO ()
- embedJsFile :: Logger -> DynFlags -> TmpFs -> UnitEnv -> FilePath -> FilePath -> IO ()
- staticInitStat :: StaticInfo -> JStat
- staticDeclStat :: StaticInfo -> JStat
- mkExportedFuns :: UnitId -> FastString -> [FastString] -> [ExportedFun]
- mkExportedModFuns :: Module -> [FastString] -> [ExportedFun]
- computeLinkDependencies :: StgToJSConfig -> UnitEnv -> LinkSpec -> FinderOpts -> FinderCache -> ArchiveCache -> IO LinkPlan
- data LinkSpec = LinkSpec {
- lks_unit_ids :: [UnitId]
- lks_obj_root_filter :: ExportedFun -> Bool
- lks_extra_roots :: Set ExportedFun
- lks_objs_hs :: [FilePath]
- lks_objs_js :: [FilePath]
- lks_objs_cc :: [FilePath]
- data LinkPlan = LinkPlan {
- lkp_block_info :: Map Module LocatedBlockInfo
- lkp_dep_blocks :: Set BlockRef
- lkp_archives :: !(Set FilePath)
- lkp_objs_js :: !(Set FilePath)
- lkp_objs_cc :: !(Set FilePath)
- emptyLinkPlan :: LinkPlan
- incrementLinkPlan :: LinkPlan -> LinkPlan -> (LinkPlan, LinkPlan)
- data ArchiveCache
- newArchiveCache :: IO ArchiveCache
Documentation
jsLinkBinary :: FinderCache -> JSLinkConfig -> StgToJSConfig -> Logger -> TmpFs -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO () Source #
:: JSLinkConfig | |
-> StgToJSConfig | |
-> Logger | |
-> TmpFs | |
-> ArchiveCache | |
-> FilePath | output file/directory |
-> LinkPlan | |
-> IO () |
link and write result to disk (jsexe directory)
embedJsFile :: Logger -> DynFlags -> TmpFs -> UnitEnv -> FilePath -> FilePath -> IO () Source #
Embed a JS file into a JS object .o file
JS files may contain option pragmas of the form: //#OPTIONS: One of those is //#OPTIONS:CPP. When it is set, we append some common CPP definitions to the file and call cpp on it.
Other options (e.g. EMCC additional flags for link time) are stored in the JS object header. See JSOptions.
staticInitStat :: StaticInfo -> JStat Source #
Initialize a global object.
All global objects have to be declared (staticInfoDecl) first.
staticDeclStat :: StaticInfo -> JStat Source #
declare and do first-pass init of a global object (create JS object for heap objects)
mkExportedFuns :: UnitId -> FastString -> [FastString] -> [ExportedFun] Source #
Given a UnitId
, a module name, and a set of symbols in the module,
package these into an ExportedFun
.
mkExportedModFuns :: Module -> [FastString] -> [ExportedFun] Source #
Given a Module
and a set of symbols in the module, package these into an
ExportedFun
.
computeLinkDependencies :: StgToJSConfig -> UnitEnv -> LinkSpec -> FinderOpts -> FinderCache -> ArchiveCache -> IO LinkPlan Source #
LinkSpec | |
|
Instances
LinkPlan | |
|
Instances
incrementLinkPlan :: LinkPlan -> LinkPlan -> (LinkPlan, LinkPlan) Source #
Given a base
link plan (assumed to be already linked) and a new
link
plan, compute `(diff, total)` link plans.
diff
is the incremental link plan to get frombase
tototal
total
is the total link plan as ifbase
andnew
were linked at once
data ArchiveCache Source #