Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ModuleGraph
- data ModuleGraphNode
- emptyMG :: ModuleGraph
- mkModuleGraph :: [ExtendedModSummary] -> ModuleGraph
- mkModuleGraph' :: [ModuleGraphNode] -> ModuleGraph
- extendMG :: ModuleGraph -> ExtendedModSummary -> ModuleGraph
- extendMGInst :: ModuleGraph -> InstantiatedUnit -> ModuleGraph
- extendMG' :: ModuleGraph -> ModuleGraphNode -> ModuleGraph
- filterToposortToModules :: [SCC ModuleGraphNode] -> [SCC ModSummary]
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- mgModSummaries :: ModuleGraph -> [ModSummary]
- mgModSummaries' :: ModuleGraph -> [ModuleGraphNode]
- mgExtendedModSummaries :: ModuleGraph -> [ExtendedModSummary]
- mgElemModule :: ModuleGraph -> Module -> Bool
- mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
- mgBootModules :: ModuleGraph -> ModuleSet
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
- showModMsg :: DynFlags -> Bool -> ModuleGraphNode -> SDoc
Documentation
data ModuleGraph Source #
A 'ModuleGraph
' contains all the nodes from the home package (only). See
'ModuleGraphNode
' for information about the nodes.
Modules need to be compiled. hs-boots need to be typechecked before the associated "real" module so modules with {-# SOURCE #-} imports can be built. Instantiations also need to be typechecked to ensure that the module fits the signature. Substantiation typechecking is roughly comparable to the check that the module and its hs-boot agree.
The graph is not necessarily stored in topologically-sorted order. Use
topSortModuleGraph
and flattenSCC
to achieve this.
data ModuleGraphNode Source #
A 'ModuleGraphNode
' is a node in the 'ModuleGraph
'.
Edges between nodes mark dependencies arising from module imports
and dependencies arising from backpack instantiations.
InstantiationNode InstantiatedUnit | Instantiation nodes track the instantiation of other units (backpack dependencies) with the holes (signatures) of the current package. |
ModuleNode ExtendedModSummary | There is a module summary node for each module, signature, and boot module being built. |
Instances
Outputable ModuleGraphNode Source # | |
Defined in GHC.Unit.Module.Graph ppr :: ModuleGraphNode -> SDoc Source # |
mkModuleGraph' :: [ModuleGraphNode] -> ModuleGraph Source #
extendMG :: ModuleGraph -> ExtendedModSummary -> ModuleGraph Source #
Add an ExtendedModSummary to ModuleGraph. Assumes that the new ModSummary is not an element of the ModuleGraph.
extendMG' :: ModuleGraph -> ModuleGraphNode -> ModuleGraph Source #
filterToposortToModules :: [SCC ModuleGraphNode] -> [SCC ModSummary] Source #
This function filters out all the instantiation nodes from each SCC of a topological sort. Use this with care, as the resulting "strongly connected components" may not really be strongly connected in a direct way, as instantiations have been removed. It would probably be best to eliminate uses of this function where possible.
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph Source #
Map a function f
over all the ModSummaries
.
To preserve invariants f
can't change the isBoot status.
mgModSummaries :: ModuleGraph -> [ModSummary] Source #
mgModSummaries' :: ModuleGraph -> [ModuleGraphNode] Source #
mgElemModule :: ModuleGraph -> Module -> Bool Source #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary Source #
Look up a ModSummary in the ModuleGraph
mgBootModules :: ModuleGraph -> ModuleSet Source #
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool Source #
Determines whether a set of modules requires Template Haskell or Quasi Quotes
Note that if the session's DynFlags
enabled Template Haskell when
depanal
was called, then each module in the returned module graph will
have Template Haskell enabled whether it is actually needed or not.
showModMsg :: DynFlags -> Bool -> ModuleGraphNode -> SDoc Source #