ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Driver.Make

Synopsis

Documentation

depanal Source #

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.

depanalE Source #

Arguments

:: GhcMonad m 
=> [ModuleName]

excluded modules

-> Bool

allow duplicate roots

-> m (ErrorMessages, ModuleGraph) 

Perform dependency analysis like in depanal. In case of errors, the errors and an empty module graph are returned.

depanalPartial Source #

Arguments

:: GhcMonad m 
=> [ModuleName]

excluded modules

-> Bool

allow duplicate roots

-> m (ErrorMessages, ModuleGraph)

possibly empty Bag of errors and a module graph.

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.

load :: GhcMonad m => LoadHowMuch -> m 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 target (see hscTarget) 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.

load' :: GhcMonad m => 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 ModuleName

Load only the given module and its dependencies.

LoadDependenciesOf ModuleName

Load only the dependencies of the given module, but not the module itself.

downsweep :: HscEnv -> [ModSummary] -> [ModuleName] -> Bool -> IO [Either ErrorMessages ModSummary] Source #

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.

topSortModuleGraph Source #

Arguments

:: Bool

Drop hi-boot nodes? (see below)

-> ModuleGraph 
-> Maybe ModuleName

Root module name. If Nothing, use the full graph.

-> [SCC ModSummary] 

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 -> [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.)

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 #-}`.

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.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsBootInterface Source #

toConstr :: IsBootInterface -> Constr Source #

dataTypeOf :: IsBootInterface -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsBootInterface) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsBootInterface) Source #

gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IsBootInterface -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

Show IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Binary IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Eq IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Ord IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types