| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Driver.Make
Synopsis
- depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph
- depanalE :: GhcMonad m => [ModuleName] -> Bool -> m (DriverMessages, ModuleGraph)
- depanalPartial :: GhcMonad m => [ModuleName] -> Bool -> m (DriverMessages, ModuleGraph)
- checkHomeUnitsClosed :: UnitEnv -> Set UnitId -> [(UnitId, UnitId)] -> [DriverMessages]
- load :: GhcMonad f => LoadHowMuch -> f SuccessFlag
- loadWithCache :: GhcMonad m => Maybe ModIfaceCache -> LoadHowMuch -> m SuccessFlag
- load' :: GhcMonad m => Maybe ModIfaceCache -> LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag
- data LoadHowMuch
- data ModIfaceCache = ModIfaceCache {- iface_clearCache :: IO [CachedIface]
- iface_addToCache :: CachedIface -> IO ()
 
- noIfaceCache :: Maybe ModIfaceCache
- newIfaceCache :: IO ModIfaceCache
- instantiationNodes :: UnitId -> UnitState -> [ModuleGraphNode]
- downsweep :: HscEnv -> [ModSummary] -> [ModuleName] -> Bool -> IO ([DriverMessages], [ModuleGraphNode])
- topSortModuleGraph :: Bool -> ModuleGraph -> Maybe HomeUnitModule -> [SCC ModuleGraphNode]
- ms_home_srcimps :: ModSummary -> [Located ModuleName]
- ms_home_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
- summariseModule :: HscEnv -> HomeUnit -> Map FilePath ModSummary -> IsBootInterface -> Located ModuleName -> PkgQual -> Maybe (StringBuffer, UTCTime) -> [ModuleName] -> IO SummariseResult
- data SummariseResult
- summariseFile :: HscEnv -> HomeUnit -> Map FilePath ModSummary -> FilePath -> Maybe Phase -> Maybe (StringBuffer, UTCTime) -> IO (Either DriverMessages ModSummary)
- hscSourceToIsBoot :: HscSource -> IsBootInterface
- findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [ModuleName]
- implicitRequirementsShallow :: HscEnv -> [(PkgQual, Located ModuleName)] -> IO ([ModuleName], [InstantiatedUnit])
- noModError :: HscEnv -> SrcSpan -> ModuleName -> FindResult -> MsgEnvelope GhcMessage
- cyclicModuleErr :: [ModuleGraphNode] -> SDoc
- type SummaryNode = Node Int ModuleGraphNode
- data IsBootInterface
- mkNodeKey :: ModuleGraphNode -> NodeKey
- type ModNodeKey = ModuleNameWithIsBoot
- data ModNodeKeyWithUid = ModNodeKeyWithUid {}
- newtype ModNodeMap a = ModNodeMap {- unModNodeMap :: Map ModNodeKey a
 
- emptyModNodeMap :: ModNodeMap a
- modNodeMapElems :: ModNodeMap a -> [a]
- modNodeMapLookup :: ModNodeKey -> ModNodeMap a -> Maybe a
- modNodeMapInsert :: ModNodeKey -> a -> ModNodeMap a -> ModNodeMap a
- modNodeMapSingleton :: ModNodeKey -> a -> ModNodeMap a
- modNodeMapUnionWith :: (a -> a -> a) -> ModNodeMap a -> ModNodeMap a -> ModNodeMap a
Documentation
Arguments
| :: GhcMonad m | |
| => [ModuleName] | excluded modules | 
| -> Bool | allow duplicate roots | 
| -> m ModuleGraph | 
Perform a dependency analysis starting from the current targets and update the session with the new module graph.
Dependency analysis entails parsing the import directives and may
 therefore require running certain preprocessors.
Note that each ModSummary in the module graph caches its DynFlags.
 These DynFlags are determined by the current session DynFlags and the
 OPTIONS and LANGUAGE pragmas of the parsed module.  Thus if you want
 changes to the DynFlags to take effect you need to call this function
 again.
 In case of errors, just throw them.
Arguments
| :: GhcMonad m | |
| => [ModuleName] | excluded modules | 
| -> Bool | allow duplicate roots | 
| -> m (DriverMessages, ModuleGraph) | 
Perform dependency analysis like in depanal.
 In case of errors, the errors and an empty module graph are returned.
Arguments
| :: GhcMonad m | |
| => [ModuleName] | excluded modules | 
| -> Bool | allow duplicate roots | 
| -> m (DriverMessages, ModuleGraph) | possibly empty  | 
Perform dependency analysis like depanal but return a partial module
 graph even in the face of problems with some modules.
Modules which have parse errors in the module header, failing preprocessors or other issues preventing them from being summarised will simply be absent from the returned module graph.
Unlike depanal this function will not update hsc_mod_graph with the
 new module graph.
checkHomeUnitsClosed :: UnitEnv -> Set UnitId -> [(UnitId, UnitId)] -> [DriverMessages] Source #
load :: GhcMonad f => LoadHowMuch -> f SuccessFlag Source #
Try to load the program.  See LoadHowMuch for the different modes.
This function implements the core of GHC's --make mode.  It preprocesses,
 compiles and loads the specified modules, avoiding re-compilation wherever
 possible.  Depending on the backend (see backend field) compiling
 and loading may result in files being created on disk.
Calls the defaultWarnErrLogger after each compiling each module, whether
 successful or not.
If errors are encountered during dependency analysis, the module depanalE
 returns together with the errors an empty ModuleGraph.
 After processing this empty ModuleGraph, the errors of depanalE are thrown.
 All other errors are reported using the defaultWarnErrLogger.
loadWithCache :: GhcMonad m => Maybe ModIfaceCache -> LoadHowMuch -> m SuccessFlag Source #
load' :: GhcMonad m => Maybe ModIfaceCache -> LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag Source #
Generalized version of load which also supports a custom
 Messager (for reporting progress) and ModuleGraph (generally
 produced by calling depanal.
data LoadHowMuch Source #
Describes which modules of the module graph need to be loaded.
Constructors
| LoadAllTargets | Load all targets and its dependencies. | 
| LoadUpTo HomeUnitModule | Load only the given module and its dependencies. | 
| LoadDependenciesOf HomeUnitModule | Load only the dependencies of the given module, but not the module itself. | 
data ModIfaceCache Source #
Constructors
| ModIfaceCache | |
| Fields 
 | |
instantiationNodes :: UnitId -> UnitState -> [ModuleGraphNode] Source #
Collect the instantiations of dependencies to create InstantiationNode work graph nodes.
 These are used to represent the type checking that is done after
 all the free holes (sigs in current package) relevant to that instantiation
 are compiled. This is necessary to catch some instantiation errors.
In the future, perhaps more of the work of instantiation could be moved here, instead of shoved in with the module compilation nodes. That could simplify backpack, and maybe hs-boot too.
Arguments
| :: HscEnv | |
| -> [ModSummary] | Old summaries | 
| -> [ModuleName] | |
| -> Bool | |
| -> IO ([DriverMessages], [ModuleGraphNode]) | 
Downsweep (dependency analysis)
Chase downwards from the specified root set, returning summaries for all home modules encountered. Only follow source-import links.
We pass in the previous collection of summaries, which is used as a cache to avoid recalculating a module summary if the source is unchanged.
The returned list of [ModSummary] nodes has one node for each home-package module, plus one for any hs-boot files. The imports of these nodes are all there, including the imports of non-home-package modules.
Arguments
| :: Bool | Drop hi-boot nodes? (see below) | 
| -> ModuleGraph | |
| -> Maybe HomeUnitModule | Root module name.  If  | 
| -> [SCC ModuleGraphNode] | 
Topological sort of the module graph
Calculate SCCs of the module graph, possibly dropping the hi-boot nodes The resulting list of strongly-connected-components is in topologically sorted order, starting with the module(s) at the bottom of the dependency graph (ie compile them first) and ending with the ones at the top.
Drop hi-boot nodes (first boolean arg)?
- False: treat the hi-boot summaries as nodes of the graph, so the graph must be acyclic
- True: eliminate the hi-boot nodes, and instead pretend the a source-import of Foo is an import of Foo The resulting graph has no hi-boot nodes, but can be cyclic
ms_home_srcimps :: ModSummary -> [Located ModuleName] Source #
Like ms_home_imps, but for SOURCE imports.
ms_home_imps :: ModSummary -> [(PkgQual, Located ModuleName)] Source #
All of the (possibly) home module imports from a
 ModSummary; that is to say, each of these module names
 could be a home import if an appropriately named file
 existed.  (This is in contrast to package qualified
 imports, which are guaranteed not to be home imports.)
Arguments
| :: HscEnv | |
| -> HomeUnit | |
| -> Map FilePath ModSummary | Map of old summaries | 
| -> IsBootInterface | |
| -> Located ModuleName | |
| -> PkgQual | |
| -> Maybe (StringBuffer, UTCTime) | |
| -> [ModuleName] | |
| -> IO SummariseResult | 
data SummariseResult Source #
summariseFile :: HscEnv -> HomeUnit -> Map FilePath ModSummary -> FilePath -> Maybe Phase -> Maybe (StringBuffer, UTCTime) -> IO (Either DriverMessages ModSummary) Source #
hscSourceToIsBoot :: HscSource -> IsBootInterface Source #
Tests if an HscSource is a boot file, primarily for constructing elements
 of BuildModule. We conflate signatures and modules because they are bound
 in the same namespace; only boot interfaces can be disambiguated with
 `import {-# SOURCE #-}`.
findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [ModuleName] Source #
For a module modname of type HscSource, determine the list
 of extra "imports" of other requirements which should be considered part of
 the import of the requirement, because it transitively depends on those
 requirements by imports of modules from other packages.  The situation
 is something like this:
unit p where signature X signature Y import X
unit q where dependency p[X=<A>,Y=<B>] signature A signature B
Although q's B does not directly import A, we still have to make sure we process A first, because the merging process will cause B to indirectly import A. This function finds the TRANSITIVE closure of all such imports we need to make.
implicitRequirementsShallow :: HscEnv -> [(PkgQual, Located ModuleName)] -> IO ([ModuleName], [InstantiatedUnit]) Source #
Like implicitRequirements', but returns either the module name, if it is
 a free hole, or the instantiated unit the imported module is from, so that
 that instantiated unit can be processed and via the batch mod graph (rather
 than a transitive closure done here) all the free holes are still reachable.
noModError :: HscEnv -> SrcSpan -> ModuleName -> FindResult -> MsgEnvelope GhcMessage Source #
cyclicModuleErr :: [ModuleGraphNode] -> SDoc Source #
type SummaryNode = Node Int ModuleGraphNode Source #
data IsBootInterface Source #
Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.
Instances
mkNodeKey :: ModuleGraphNode -> NodeKey Source #
type ModNodeKey = ModuleNameWithIsBoot Source #
data ModNodeKeyWithUid Source #
Constructors
| ModNodeKeyWithUid | |
| Fields | |
Instances
| Outputable ModNodeKeyWithUid Source # | |
| Defined in GHC.Unit.Module.Graph Methods ppr :: ModNodeKeyWithUid -> SDoc Source # | |
| Eq ModNodeKeyWithUid Source # | |
| Defined in GHC.Unit.Module.Graph Methods (==) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # (/=) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # | |
| Ord ModNodeKeyWithUid Source # | |
| Defined in GHC.Unit.Module.Graph Methods compare :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Ordering # (<) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # (<=) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # (>) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # (>=) :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> Bool # max :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> ModNodeKeyWithUid # min :: ModNodeKeyWithUid -> ModNodeKeyWithUid -> ModNodeKeyWithUid # | |
newtype ModNodeMap a Source #
Constructors
| ModNodeMap | |
| Fields 
 | |
Instances
emptyModNodeMap :: ModNodeMap a Source #
modNodeMapElems :: ModNodeMap a -> [a] Source #
modNodeMapLookup :: ModNodeKey -> ModNodeMap a -> Maybe a Source #
modNodeMapInsert :: ModNodeKey -> a -> ModNodeMap a -> ModNodeMap a Source #
modNodeMapSingleton :: ModNodeKey -> a -> ModNodeMap a Source #
modNodeMapUnionWith :: (a -> a -> a) -> ModNodeMap a -> ModNodeMap a -> ModNodeMap a Source #