ghc-simple-0.1.0.0: Simplified interface to the GHC API.

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GHC.Simple

Description

Simplified interface to the GHC API.

Synopsis

Documentation

class Compile a Source

Any type we can generate intermediate code for.

Minimal complete definition

toCode

type StgModule = CompiledModule [StgBinding] Source

module CoreSyn

module StgSyn

module Module

module Id

module IdInfo

module Var

module Literal

module DataCon

module OccName

module Name

module Type

module TysPrim

module TyCon

module PrimOp

module DynFlags

module SrcLoc

data ModSummary :: *

A single node in a 'ModuleGraph. The nodes of the module graph are one of:

  • A regular Haskell source module
  • A hi-boot source module
  • An external-core source module

Constructors

ModSummary 

Fields

ms_mod :: Module

Identity of the module

ms_hsc_src :: HscSource

The module source either plain Haskell, hs-boot or external core

ms_location :: ModLocation

Location of the various files belonging to the module

ms_hs_date :: UTCTime

Timestamp of source file

ms_obj_date :: Maybe UTCTime

Timestamp of object, if we have one

ms_srcimps :: [Located (ImportDecl RdrName)]

Source imports of the module

ms_textual_imps :: [Located (ImportDecl RdrName)]

Non-source imports of the module from the module *text*

ms_hspp_file :: FilePath

Filename of preprocessed source file

ms_hspp_opts :: DynFlags

Cached flags from OPTIONS, INCLUDE and LANGUAGE pragmas in the modules source code

ms_hspp_buf :: Maybe StringBuffer

The actual preprocessed source, if we have it

data ModGuts :: *

A ModGuts is carried through the compiler, accumulating stuff as it goes There is only one ModGuts at any time, the one for the module being compiled right now. Once it is compiled, a ModIface and ModDetails are extracted and the ModGuts is discarded.

Constructors

ModGuts 

Fields

mg_module :: !Module

Module being compiled

mg_boot :: IsBootInterface

Whether it's an hs-boot module

mg_exports :: ![AvailInfo]

What it exports

mg_deps :: !Dependencies

What it depends on, directly or otherwise

mg_dir_imps :: !ImportedMods

Directly-imported modules; used to generate initialisation code

mg_used_names :: !NameSet

What the module needed (used in mkIface)

mg_used_th :: !Bool

Did we run a TH splice?

mg_rdr_env :: !GlobalRdrEnv

Top-level lexical environment

mg_fix_env :: !FixityEnv

Fixities declared in this module ToDo: I'm unconvinced this is actually used anywhere

mg_tcs :: ![TyCon]

TyCons declared in this module (includes TyCons for classes)

mg_insts :: ![ClsInst]

Class instances declared in this module

mg_fam_insts :: ![FamInst]

Family instances declared in this module

mg_patsyns :: ![PatSyn]

Pattern synonyms declared in this module

mg_rules :: ![CoreRule]

Before the core pipeline starts, contains See Note [Overall plumbing for rules] in Rules.lhs

mg_binds :: !CoreProgram

Bindings for this module

mg_foreign :: !ForeignStubs

Foreign exports declared in this module

mg_warns :: !Warnings

Warnings declared in the module

mg_anns :: [Annotation]

Annotations declared in this module

mg_hpc_info :: !HpcInfo

Coverage tick boxes in the module

mg_modBreaks :: !ModBreaks

Breakpoints for the module

mg_vect_decls :: ![CoreVect]

Vectorisation declarations in this module (produced by desugarer & consumed by vectoriser)

mg_vect_info :: !VectInfo

Pool of vectorised declarations in the module

mg_inst_env :: InstEnv

Class instance environment from home-package modules (including this one); c.f. tcg_inst_env

mg_fam_inst_env :: FamInstEnv

Type-family instance environment for home-package modules (including this one); c.f. tcg_fam_inst_env

mg_safe_haskell :: SafeHaskellMode

Safe Haskell mode

mg_trust_pkg :: Bool

Do we need to trust our own package for Safe Haskell? See Note [RnNames . Trust Own Package]

mg_dependent_files :: [FilePath]

dependencies from addDependentFile

Instances

type PkgKey = PackageId Source

Synonym for PackageId, to bridge a slight incompatibility between GHC 7.8 and 7.10.

pkgKeyString :: PkgKey -> String Source

String representation of a package ID/key.

modulePkgKey :: Module -> PkgKey Source

Package ID/key of a module.

compile Source

Arguments

:: Compile a 
=> [String]

List of compilation targets. A target can be either a module or a file name.

-> IO (CompResult a) 

Compile a list of targets and their dependencies into intermediate code. Uses settings from the the default CompConfig.

compileWith Source

Arguments

:: Compile a 
=> CompConfig

GHC pipeline configuration.

-> [String]

List of compilation targets. A target can be either a module or a file name. Targets may also be read from the specified CompConfig, if cfgUseTargetsFromFlags is set.

-> IO (CompResult a) 

Compile a list of targets and their dependencies using a custom configuration.

genericCompile Source

Arguments

:: (DynFlags -> ModSummary -> Ghc a)

Compilation function.

-> CompConfig

GHC pipeline configuration.

-> [String]

List of compilation targets. A target can be either a module or a file name. Targets may also be read from the specified CompConfig, if cfgUseTargetsFromFlags is set.

-> IO (CompResult a) 

Compile a list of targets and their dependencies using a custom configuration and compilation function in the Ghc monad. See Language.Haskell.GHC.Simple.Impl for more information about building custom compilation functions.