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

GHC.Driver.Main

Description

Main API for compiling plain Haskell source code.

This module implements compilation of a Haskell source. It is not concerned with preprocessing of source files; this is handled in GHC.Driver.Pipeline

There are various entry points depending on what mode we're in: "batch" mode (--make), "one-shot" mode (-c, -S etc.), and "interactive" mode (GHCi). There are also entry points for individual passes: parsing, typechecking/renaming, desugaring, and simplification.

All the functions here take an HscEnv as a parameter, but none of them return a new one: HscEnv is treated as an immutable value from here on in (although it has mutable components, for the caches).

We use the Hsc monad to deal with warning messages consistently: specifically, while executing within an Hsc monad, warnings are collected. When a Hsc monad returns to an IO monad, the warnings are printed, or compilation aborts if the -Werror flag is enabled.

(c) The GRASP/AQUA Project, Glasgow University, 1993-2000

Synopsis

Making an HscEnv

initHscEnv :: Maybe FilePath -> IO HscEnv Source #

Initialize HscEnv from an optional top_dir path

Compiling complete source files

data HscBackendAction Source #

Action to perform in backend compilation

Constructors

HscUpdate ModIface

Update the boot and signature file results.

HscRecomp

Recompile this module.

Fields

Instances

Instances details
Outputable HscBackendAction Source # 
Instance details

Defined in GHC.Unit.Module.Status

data HscRecompStatus Source #

Status of a module in incremental compilation

Constructors

HscUpToDate ModIface HomeModLinkable

Nothing to do because code already exists.

HscRecompNeeded (Maybe Fingerprint)

Recompilation of module, or update of interface is required. Optionally pass the old interface hash to avoid updating the existing interface when it has not changed.

hscMaybeWriteIface Source #

Arguments

:: Logger 
-> DynFlags 
-> Bool

Is this a simple interface generated after the core pipeline, or one with information from the backend? See: Note [Writing interface files]

-> ModIface 
-> Maybe Fingerprint

The old interface hash, used to decide if we need to actually write the new interface.

-> ModLocation 
-> IO () 

Write interface files

hscGenHardCode Source #

Arguments

:: HscEnv 
-> CgGuts 
-> ModLocation 
-> FilePath 
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)], Maybe StgCgInfos, Maybe CmmCgInfos)

Just f = _stub.c is f

Compile to hard-code.

Running passes separately

hscRecompStatus :: Maybe Messager -> HscEnv -> ModSummary -> Maybe ModIface -> HomeModLinkable -> (Int, Int) -> IO HscRecompStatus Source #

Do the recompilation avoidance checks for both one-shot and --make modes This function is the *only* place in the compiler where we decide whether to recompile a module or not!

hscParse :: HscEnv -> ModSummary -> IO HsParsedModule Source #

parse a file, returning the abstract syntax

hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) Source #

Rename and typecheck a module, additionally returning the renamed syntax

hscTypecheckAndGetWarnings :: HscEnv -> ModSummary -> IO (FrontendResult, WarningMessages) Source #

Do Typechecking without throwing SourceError exception with -Werror

hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts Source #

Convert a typechecked module to Core

makeSimpleDetails :: Logger -> TcGblEnv -> IO ModDetails Source #

Make a ModDetails from the results of typechecking. Used when typechecking only, as opposed to full compilation.

hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts Source #

Run Core2Core simplifier. The list of String is a list of (Core) plugin module names added via TH (cf addCorePlugin).

Safe Haskell

hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool Source #

Check that a module is safe to import.

We return True to indicate the import is safe and False otherwise although in the False case an exception may be thrown first.

hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, Set UnitId) Source #

Return if a module is trusted and the pkgs it depends on to be trusted.

Support for interactive evaluation

hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv Source #

Rename some import declarations

hscTcRnLookupRdrName :: HscEnv -> LocatedN RdrName -> IO (NonEmpty Name) Source #

Lookup things in the compiler's environment

hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv)) Source #

Compile a stmt all the way to an HValue, but don't run it

We return Nothing to indicate an empty statement (or comment only), not a parse error.

hscStmtWithLocation Source #

Arguments

:: HscEnv 
-> String

The statement

-> String

The source

-> Int

Starting line

-> IO (Maybe ([Id], ForeignHValue, FixityEnv)) 

Compile a stmt all the way to an HValue, but don't run it

We return Nothing to indicate an empty statement (or comment only), not a parse error.

hscParsedStmt Source #

Arguments

:: HscEnv 
-> GhciLStmt GhcPs

The parsed statement

-> IO (Maybe ([Id], ForeignHValue, FixityEnv)) 

hscDecls Source #

Arguments

:: HscEnv 
-> String

The statement

-> IO ([TyThing], InteractiveContext) 

Compile a decls

hscDeclsWithLocation Source #

Arguments

:: HscEnv 
-> String

The statement

-> String

The source

-> Int

Starting line

-> IO ([TyThing], InteractiveContext) 

Compile a decls

hscTcExpr Source #

Arguments

:: HscEnv 
-> TcRnExprMode 
-> String

The expression

-> IO Type 

Typecheck an expression (but don't run it)

data TcRnExprMode Source #

How should we infer a type? See Note [TcRnExprMode]

Constructors

TM_Inst

Instantiate inferred quantifiers only (:type)

TM_Default

Instantiate all quantifiers, and do eager defaulting (:type +d)

hscKcType Source #

Arguments

:: HscEnv 
-> Bool

Normalise the type

-> String

The type as a string

-> IO (Type, Kind)

Resulting type (possibly normalised) and kind

Find the kind of a type, after generalisation

Low-level exports for hooks

hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts Source #

Run Core2Core simplifier. The list of String is a list of (Core) plugin module names added via TH (cf addCorePlugin).

doCodeGen Source #

Arguments

:: HscEnv 
-> Module 
-> InfoTableProvMap 
-> [TyCon] 
-> CollectedCCs 
-> [CgStgTopBinding]

Bindings come already annotated with fvs

-> HpcInfo 
-> IO (Stream IO CmmGroupSRTs CmmCgInfos) 

ioMsgMaybe :: IO (Messages GhcMessage, Maybe a) -> Hsc a Source #

Deal with errors and warnings returned by a compilation step

In order to reduce dependencies to other parts of the compiler, functions outside the "main" parts of GHC return warnings and errors as a parameter and signal success via by wrapping the result in a Maybe type. This function logs the returned warnings and propagates errors as exceptions (of type SourceError).

This function assumes the following invariants:

  1. If the second result indicates success (is of the form 'Just x'), there must be no error messages in the first result.
  2. If there are no error messages, but the second result indicates failure there should be warnings in the first result. That is, if the action failed, it must have been due to the warnings (i.e., -Werror).

hscAddSptEntries :: HscEnv -> [SptEntry] -> IO () Source #

Load the given static-pointer table entries into the interpreter. See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.