ghc-7.8.3: The GHC API

Safe HaskellNone
LanguageHaskell98

HscMain

Contents

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 DriverPipeline.

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

Warning messages are dealt with consistently throughout this API: during compilation warnings are collected, and before any function in HscMain returns, the warnings are either printed, or turned into a real compialtion error if the -Werror flag is enabled.

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

Synopsis

Making an HscEnv

Compiling complete source files

data HscStatus Source

Status of a compilation to hard-code

hscGenHardCode Source

Arguments

:: HscEnv 
-> CgGuts 
-> ModSummary 
-> FilePath 
-> IO (FilePath, Maybe FilePath)

Just f = _stub.c is f

Compile to hard-code.

Running passes separately

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

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

Convert a typechecked module to Core

makeSimpleIface :: HscEnv -> Maybe ModIface -> TcGblEnv -> ModDetails -> IO (ModIface, Bool) Source

Make a ModIface from the results of typechecking. Used when not optimising, and the interface doesn't need to contain any unfoldings or other cross-module optimisation info. ToDo: the old interface is only needed to get the version numbers, we should use fingerprint versions instead.

makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails Source

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

Support for interactive evaluation

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, [PackageId]) Source

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

hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv Source

Rename some import declarations

hscTcRnLookupRdrName :: HscEnv -> RdrName -> IO [Name] Source

Lookup things in the compiler's environment

hscStmt :: HscEnv -> String -> IO (Maybe ([Id], IO [HValue], 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], IO [HValue], 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.

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 
-> String

The expression

-> IO Type 

Typecheck an expression (but don't run it) Returns its most general type

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 Currently this does *not* generalise the kinds of the type

Low-level exports for hooks