ghc-7.4.1: The GHC API

Safe HaskellSafe-Infered

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

type Compiler result = HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> Maybe (Int, Int) -> IO resultSource

data HscStatus' a Source

Status of a compilation to hard-code or nothing.

Constructors

HscNoRecomp 
HscRecomp (Maybe FilePath) a 

hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)Source

Compile Haskell, boot and extCore in batch mode.

Running passes separately

hscParse :: HscEnv -> ModSummary -> IO HsParsedModuleSource

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 ModGutsSource

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 ModDetailsSource

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

Backends

Support for interactive evaluation

hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO (Maybe PackageId)Source

Check that a module is safe to import.

We return a package id if the safe import is OK and a Nothing otherwise with the reason for the failure printed out.

hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnvSource

Rename some import declarations

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

Lookup things in the compiler's environment

hscStmtSource

Arguments

:: HscEnv 
-> String

The statement

-> IO (Maybe ([Id], HValue))

Nothing == empty statement (or comment only), but no parse error

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

hscStmtWithLocationSource

Arguments

:: HscEnv 
-> String

The statement

-> String

The source

-> Int

Starting line

-> IO (Maybe ([Id], HValue))

Nothing == empty statement (or comment only), but no parse error

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

hscDeclsSource

Arguments

:: HscEnv 
-> String

The statement

-> IO ([TyThing], InteractiveContext) 

Compile a decls

hscDeclsWithLocationSource

Arguments

:: HscEnv 
-> String

The statement

-> String

The source

-> Int

Starting line

-> IO ([TyThing], InteractiveContext) 

Compile a decls

hscTcExprSource

Arguments

:: HscEnv 
-> String

The expression

-> IO Type 

Typecheck an expression (but don't run it)

hscKcTypeSource

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