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 | Haskell2010 |
GHCJS linker, collects dependencies from the object files which contain linkable units with dependency information
Synopsis
- jsLinkBinary :: FinderCache -> JSLinkConfig -> StgToJSConfig -> [FilePath] -> Logger -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO ()
- jsLink :: JSLinkConfig -> StgToJSConfig -> Logger -> 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 -> IO LinkPlan
- data LinkSpec = LinkSpec {
- lks_unit_ids :: [UnitId]
- lks_obj_files :: [LinkedObj]
- lks_obj_root_filter :: ExportedFun -> Bool
- lks_extra_roots :: Set ExportedFun
- lks_extra_js :: [FilePath]
- data LinkPlan = LinkPlan {}
- emptyLinkPlan :: LinkPlan
- incrementLinkPlan :: LinkPlan -> LinkPlan -> (LinkPlan, LinkPlan)
Documentation
jsLinkBinary :: FinderCache -> JSLinkConfig -> StgToJSConfig -> [FilePath] -> Logger -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO () Source #
:: JSLinkConfig | |
-> StgToJSConfig | |
-> Logger | |
-> 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 .o file
The JS file is merely copied into a .o file with an additional header ("//Javascript") in order to be recognized later on.
JS files may contain option pragmas of the form: //#OPTIONS: For now, only the CPP option is supported. If the CPP option is set, we append some common CPP definitions to the file and call cpp on it.
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 -> 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