| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GhcMake
Synopsis
- depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph
- load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
- load' :: GhcMonad m => LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag
- data LoadHowMuch
- topSortModuleGraph :: Bool -> ModuleGraph -> Maybe ModuleName -> [SCC ModSummary]
- ms_home_srcimps :: ModSummary -> [Located ModuleName]
- ms_home_imps :: ModSummary -> [Located ModuleName]
- data IsBoot
- summariseModule :: HscEnv -> NodeMap ModSummary -> IsBoot -> Located ModuleName -> Bool -> Maybe (StringBuffer, UTCTime) -> [ModuleName] -> IO (Maybe (Either ErrMsg ModSummary))
- hscSourceToIsBoot :: HscSource -> IsBoot
- findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [(Maybe FastString, Located ModuleName)]
- implicitRequirements :: HscEnv -> [(Maybe FastString, Located ModuleName)] -> IO [(Maybe FastString, Located ModuleName)]
- noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> ErrMsg
- cyclicModuleErr :: [ModSummary] -> SDoc
- moduleGraphNodes :: Bool -> [ModSummary] -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode)
- type SummaryNode = Node Int ModSummary
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.
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.
Throw a SourceError if errors are encountered before the actual
 compilation starts (e.g., during dependency analysis).  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. | 
Arguments
| :: Bool | Drop hi-boot nodes? (see below) | 
| -> ModuleGraph | |
| -> Maybe ModuleName | Root module name.  If  | 
| -> [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.)
Bool indicating if a module is a boot module or not.  We need to treat
 boot modules specially when building compilation graphs, since they break
 cycles.  Regular source files and signature files are treated equivalently.
summariseModule :: HscEnv -> NodeMap ModSummary -> IsBoot -> Located ModuleName -> Bool -> Maybe (StringBuffer, UTCTime) -> [ModuleName] -> IO (Maybe (Either ErrMsg ModSummary)) Source #
hscSourceToIsBoot :: HscSource -> IsBoot Source #
Tests if an HscSource is a boot file, primarily for constructing
 elements of BuildModule.
findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [(Maybe FastString, Located ModuleName)] Source #
findExtraSigImports, but in a convenient form for GhcMake and
 TcRnDriver.
implicitRequirements :: HscEnv -> [(Maybe FastString, Located ModuleName)] -> IO [(Maybe FastString, Located ModuleName)] Source #
noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> ErrMsg Source #
cyclicModuleErr :: [ModSummary] -> SDoc Source #
moduleGraphNodes :: Bool -> [ModSummary] -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode) Source #
type SummaryNode = Node Int ModSummary Source #