ghc-7.0.3: The GHC API

GHC

Contents

Synopsis

Initialisation

defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m aSource

Install some default exception handlers and run the inner computation. Unless you want to handle exceptions yourself, you should wrap this around the top level of your program. The default handlers output the error message(s) to stderr and exit cleanly.

defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m aSource

Install a default cleanup handler to remove temporary files deposited by a GHC run. This is seperate from defaultErrorHandler, because you might want to override the error handling, but still get the ordinary cleanup behaviour.

GHC Monad

data Ghc a Source

A minimal implementation of a GhcMonad. If you need a custom monad, e.g., to maintain additional state consider wrapping this monad or using GhcT.

data GhcT m a Source

A monad transformer to add GHC specific features to another monad.

Note that the wrapped monad must support IO and handling of exceptions.

Instances

class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m whereSource

A monad that has all the features needed by GHC API calls.

In short, a GHC monad

  • allows embedding of IO actions,
  • can log warnings,
  • allows handling of (extensible) exceptions, and
  • maintains a current session.

If you do not use Ghc or GhcT, make sure to call GHC.initGhcMonad before any call to the GHC API functions can occur.

Instances

runGhcSource

Arguments

:: Maybe FilePath

See argument to initGhcMonad.

-> Ghc a

The action to perform.

-> IO a 

Run function for the Ghc monad.

It initialises the GHC session and warnings via initGhcMonad. Each call to this function will create a new session which should not be shared among several threads.

Any errors not handled inside the Ghc action are propagated as IO exceptions.

runGhcTSource

Arguments

:: (ExceptionMonad m, Functor m, MonadIO m) 
=> Maybe FilePath

See argument to initGhcMonad.

-> GhcT m a

The action to perform.

-> m a 

Run function for GhcT monad transformer.

It initialises the GHC session and warnings via initGhcMonad. Each call to this function will create a new session which should not be shared among several threads.

initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()Source

Initialise a GHC session.

If you implement a custom GhcMonad you must call this function in the monad run function. It will initialise the session variable and clear all warnings.

The first argument should point to the directory where GHC's library files reside. More precisely, this should be the output of ghc --print-libdir of the version of GHC the module using this API is compiled with. For portability, you should use the ghc-paths package, available at http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths.

gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m aSource

Generalised version of catch, allowing an arbitrary exception handling monad instead of just IO.

gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m cSource

Generalised version of bracket, allowing an arbitrary exception handling monad instead of just IO.

gfinally :: ExceptionMonad m => m a -> m b -> m aSource

Generalised version of finally, allowing an arbitrary exception handling monad instead of just IO.

clearWarnings :: WarnLogMonad m => m ()Source

Clear the log of Warnings.

hasWarnings :: WarnLogMonad m => m BoolSource

Returns true if there were any warnings.

printExceptionAndWarnings :: GhcMonad m => SourceError -> m ()Source

Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.

printWarnings :: GhcMonad m => m ()Source

Print all accumulated warnings using log_action.

handleSourceErrorSource

Arguments

:: ExceptionMonad m 
=> (SourceError -> m a)

exception handler

-> m a

action to perform

-> m a 

Perform the given action and call the exception handler if the action throws a SourceError. See SourceError for more information.

data GhcApiCallbacks Source

These functions are called in various places of the GHC API.

API clients can override any of these callbacks to change GHC's default behaviour.

Constructors

GhcApiCallbacks 

Fields

reportModuleCompilationResult :: GhcMonad m => ModSummary -> Maybe SourceError -> m ()

Called by load after the compilating of each module.

The default implementation simply prints all warnings and errors to stderr. Don't forget to call clearWarnings when implementing your own call.

The first argument is the module that was compiled.

The second argument is Nothing if no errors occured, but there may have been warnings. If it is Just err at least one error has occured. If srcErrorMessages is empty, compilation failed due to -Werror.

needsTemplateHaskell :: ModuleGraph -> BoolSource

Determines whether a set of modules requires Template Haskell.

Note that if the session's DynFlags enabled Template Haskell when depanal was called, then each module in the returned module graph will have Template Haskell enabled whether it is actually needed or not.

Flags and settings

data DynFlags Source

Contains not only a collection of DynFlags but also a plethora of information relating to the compilation of a single file or GHC session

Constructors

DynFlags 

Fields

ghcMode :: GhcMode
 
ghcLink :: GhcLink
 
hscTarget :: HscTarget
 
hscOutName :: String

Name of the output file

extCoreName :: String

Name of the .hcr output file

verbosity :: Int

Verbosity level: see Note [Verbosity levels]

optLevel :: Int

Optimisation level

simplPhases :: Int

Number of simplifier phases

maxSimplIterations :: Int

Max simplifier iterations

shouldDumpSimplPhase :: Maybe String
 
ruleCheck :: Maybe String
 
strictnessBefore :: [Int]

Additional demand analysis

specConstrThreshold :: Maybe Int

Threshold for SpecConstr

specConstrCount :: Maybe Int

Max number of specialisations for any one function

liberateCaseThreshold :: Maybe Int

Threshold for LiberateCase

floatLamArgs :: Maybe Int

Arg count for lambda floating See CoreMonad.FloatOutSwitches

targetPlatform :: Platform

The platform we're compiling for. Used by the NCG.

stolen_x86_regs :: Int
 
cmdlineHcIncludes :: [String]
-#includes
importPaths :: [FilePath]
 
mainModIs :: Module
 
mainFunIs :: Maybe String
 
ctxtStkDepth :: Int

Typechecker context stack depth

dphBackend :: DPHBackend
 
thisPackage :: PackageId

name of package currently being compiled

ways :: [Way]

Way flags from the command line

buildTag :: String

The global "way" (e.g. "p" for prof)

rtsBuildTag :: String

The RTS "way"

splitInfo :: Maybe (String, Int)
 
objectDir :: Maybe String
 
dylibInstallName :: Maybe String
 
hiDir :: Maybe String
 
stubDir :: Maybe String
 
objectSuf :: String
 
hcSuf :: String
 
hiSuf :: String
 
outputFile :: Maybe String
 
outputHi :: Maybe String
 
dynLibLoader :: DynLibLoader
 
dumpPrefix :: Maybe FilePath

This is set by DriverPipeline.runPipeline based on where its output is going.

dumpPrefixForce :: Maybe FilePath

Override the dumpPrefix set by DriverPipeline.runPipeline. Set by -ddump-file-prefix

includePaths :: [String]
 
libraryPaths :: [String]
 
frameworkPaths :: [String]
 
cmdlineFrameworks :: [String]
 
tmpDir :: String
 
ghcUsagePath :: FilePath
 
ghciUsagePath :: FilePath
 
rtsOpts :: Maybe String
 
rtsOptsEnabled :: RtsOptsEnabled
 
hpcDir :: String

Path to store the .mix files

opt_L :: [String]
 
opt_P :: [String]
 
opt_F :: [String]
 
opt_c :: [String]
 
opt_m :: [String]
 
opt_a :: [String]
 
opt_l :: [String]
 
opt_windres :: [String]
 
opt_lo :: [String]
 
opt_lc :: [String]
 
pgm_L :: String
 
pgm_P :: (String, [Option])
 
pgm_F :: String
 
pgm_c :: (String, [Option])
 
pgm_m :: (String, [Option])
 
pgm_s :: (String, [Option])
 
pgm_a :: (String, [Option])
 
pgm_l :: (String, [Option])
 
pgm_dll :: (String, [Option])
 
pgm_T :: String
 
pgm_sysman :: String
 
pgm_windres :: String
 
pgm_lo :: (String, [Option])
 
pgm_lc :: (String, [Option])
 
depMakefile :: FilePath
 
depIncludePkgDeps :: Bool
 
depExcludeMods :: [ModuleName]
 
depSuffixes :: [String]
 
extraPkgConfs :: [FilePath]
 
topDir :: FilePath
 
systemPackageConfig :: FilePath

The -package-conf flags given on the command line, in the order they appeared.

packageFlags :: [PackageFlag]

The -package and -hide-package flags from the command-line

pkgDatabase :: Maybe [PackageConfig]
 
pkgState :: PackageState
 
filesToClean :: IORef [FilePath]
 
dirsToClean :: IORef (Map FilePath FilePath)
 
flags :: [DynFlag]
 
language :: Maybe Language
 
extensions :: [OnOff ExtensionFlag]
 
extensionFlags :: [ExtensionFlag]
 
log_action :: Severity -> SrcSpan -> PprStyle -> Message -> IO ()

Message output action: use ErrUtils instead of this if you can

haddockOptions :: Maybe String
 

data DynFlag Source

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_D_dump_cmm 
Opt_D_dump_cmmz 
Opt_D_dump_cmmz_pretty 
Opt_D_dump_cps_cmm 
Opt_D_dump_cvt_cmm 
Opt_D_dump_asm 
Opt_D_dump_asm_native 
Opt_D_dump_asm_liveness 
Opt_D_dump_asm_coalesce 
Opt_D_dump_asm_regalloc 
Opt_D_dump_asm_regalloc_stages 
Opt_D_dump_asm_conflicts 
Opt_D_dump_asm_stats 
Opt_D_dump_asm_expanded 
Opt_D_dump_llvm 
Opt_D_dump_cpranal 
Opt_D_dump_deriv 
Opt_D_dump_ds 
Opt_D_dump_flatC 
Opt_D_dump_foreign 
Opt_D_dump_inlinings 
Opt_D_dump_rule_firings 
Opt_D_dump_occur_anal 
Opt_D_dump_parsed 
Opt_D_dump_rn 
Opt_D_dump_simpl 
Opt_D_dump_simpl_iterations 
Opt_D_dump_simpl_phases 
Opt_D_dump_spec 
Opt_D_dump_prep 
Opt_D_dump_stg 
Opt_D_dump_stranal 
Opt_D_dump_tc 
Opt_D_dump_types 
Opt_D_dump_rules 
Opt_D_dump_cse 
Opt_D_dump_worker_wrapper 
Opt_D_dump_rn_trace 
Opt_D_dump_rn_stats 
Opt_D_dump_opt_cmm 
Opt_D_dump_simpl_stats 
Opt_D_dump_cs_trace 
Opt_D_dump_tc_trace 
Opt_D_dump_if_trace 
Opt_D_dump_splices 
Opt_D_dump_BCOs 
Opt_D_dump_vect 
Opt_D_dump_hpc 
Opt_D_dump_rtti 
Opt_D_source_stats 
Opt_D_verbose_core2core 
Opt_D_verbose_stg2stg 
Opt_D_dump_hi 
Opt_D_dump_hi_diffs 
Opt_D_dump_minimal_imports 
Opt_D_dump_mod_cycles 
Opt_D_dump_view_pattern_commoning 
Opt_D_faststring_stats 
Opt_DumpToFile

Append dump output to files instead of stdout.

Opt_D_no_debug_output 
Opt_DoCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_WarnIsError 
Opt_WarnDuplicateExports 
Opt_WarnHiShadows 
Opt_WarnImplicitPrelude 
Opt_WarnIncompletePatterns 
Opt_WarnIncompletePatternsRecUpd 
Opt_WarnMissingFields 
Opt_WarnMissingImportList 
Opt_WarnMissingMethods 
Opt_WarnMissingSigs 
Opt_WarnMissingLocalSigs 
Opt_WarnNameShadowing 
Opt_WarnOverlappingPatterns 
Opt_WarnTypeDefaults 
Opt_WarnMonomorphism 
Opt_WarnUnusedBinds 
Opt_WarnUnusedImports 
Opt_WarnUnusedMatches 
Opt_WarnWarningsDeprecations 
Opt_WarnDeprecatedFlags 
Opt_WarnDodgyExports 
Opt_WarnDodgyImports 
Opt_WarnOrphans 
Opt_WarnAutoOrphans 
Opt_WarnTabs 
Opt_WarnUnrecognisedPragmas 
Opt_WarnDodgyForeignImports 
Opt_WarnLazyUnliftedBindings 
Opt_WarnUnusedDoBind 
Opt_WarnWrongDoBind 
Opt_WarnAlternativeLayoutRuleTransitional 
Opt_PrintExplicitForalls 
Opt_Strictness 
Opt_FullLaziness 
Opt_FloatIn 
Opt_Specialise 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_LiberateCase 
Opt_SpecConstr 
Opt_DoLambdaEtaExpansion 
Opt_IgnoreAsserts 
Opt_DoEtaReduction 
Opt_CaseMerge 
Opt_UnboxStrictFields 
Opt_MethodSharing 
Opt_DictsCheap 
Opt_EnableRewriteRules 
Opt_Vectorise 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_AutoSccsOnAllToplevs 
Opt_AutoSccsOnExportedToplevs 
Opt_AutoSccsOnIndividualCafs 
Opt_Pp 
Opt_ForceRecomp 
Opt_DryRun 
Opt_DoAsmMangling 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_ReadUserPackageConf 
Opt_NoHsMain 
Opt_SplitObjs 
Opt_StgStats 
Opt_HideAllPackages 
Opt_PrintBindResult 
Opt_Haddock 
Opt_HaddockOptions 
Opt_Hpc_No_Auto 
Opt_BreakOnException 
Opt_BreakOnError 
Opt_PrintEvldWithShow 
Opt_PrintBindContents 
Opt_GenManifest 
Opt_EmbedManifest 
Opt_EmitExternalCore 
Opt_SharedImplib 
Opt_BuildingCabalPackage 
Opt_SSE2 
Opt_GhciSandbox 
Opt_RunCPS 
Opt_RunCPSZ 
Opt_ConvertToZipCfgAndBack 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_TryNewCodeGen 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepRawSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 

Instances

data HscTarget Source

The target code type of the compilation (if any).

Whenever you change the target, also make sure to set ghcLink to something sensible.

HscNothing can be used to avoid generating any output, however, note that:

  • This will not run the desugaring step, thus no warnings generated in this step will be output. In particular, this includes warnings related to pattern matching. You can run the desugarer manually using GHC.desugarModule.
  • If a program uses Template Haskell the typechecker may try to run code from an imported module. This will fail if no code has been generated for this module. You can use GHC.needsTemplateHaskell to detect whether this might be the case and choose to either switch to a different target or avoid typechecking such modules. (The latter may preferable for security reasons.)

Constructors

HscC

Generate C code.

HscAsm

Generate assembly using the native code generator.

HscLlvm

Generate assembly using the llvm code generator.

HscJava

Generate Java bytecode.

HscInterpreted

Generate bytecode. (Requires LinkInMemory)

HscNothing

Don't generate any code. See notes above.

dopt :: DynFlag -> DynFlags -> BoolSource

Test whether a DynFlag is set

data GhcMode Source

The GhcMode tells us whether we're doing multi-module compilation (controlled via the GHC API) or one-shot (single-module) compilation. This makes a difference primarily to the Finder: in one-shot mode we look for interface files for imported modules, but in multi-module mode we look for source files in order to check whether they need to be recompiled.

Constructors

CompManager

--make, GHCi, etc.

OneShot
ghc -c Foo.hs
MkDepend

ghc -M, see Finder for why we need this

data GhcLink Source

What to do in the link step, if there is one.

Constructors

NoLink

Don't link at all

LinkBinary

Link object code into a binary

LinkInMemory

Use the in-memory dynamic linker (works for both bytecode and object code).

LinkDynLib

Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)

defaultObjectTarget :: HscTargetSource

The HscTarget value corresponding to the default way to create object files on the current platform.

parseDynamicFlagsSource

Arguments

:: Monad m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Located String])

Updated DynFlags, left-over arguments, and list of warnings.

Parse dynamic flags from a list of command line arguments. Returns the the parsed DynFlags, the left-over arguments, and a list of warnings. Throws a UsageError if errors occurred during parsing (such as unknown flags or missing arguments).

getSessionDynFlags :: GhcMonad m => m DynFlagsSource

Grabs the DynFlags from the Session

setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId]Source

Updates the DynFlags in a Session. This also reads the package database (unless it has already been read), and prepares the compilers knowledge about packages. It can be called again to load new packages: just add new package flags to (packageFlags dflags).

Returns a list of new packages that may need to be linked in using the dynamic linker (see linkPackages) as a result of new package flags. If you are not doing linking or doing static linking, you can ignore the list of packages returned.

parseStaticFlags :: [Located String] -> IO ([Located String], [Located String])Source

Parses GHC's static flags from a list of command line arguments.

These flags are static in the sense that they can be set only once and they are global, meaning that they affect every instance of GHC running; multiple GHC threads will use the same flags.

This function must be called before any session is started, i.e., before the first call to GHC.withGhc.

Static flags are more of a hack and are static for more or less historical reasons. In the long run, most static flags should eventually become dynamic flags.

XXX: can we add an auto-generated list of static flags here?

Targets

data Target Source

A compilation target.

A target may be supplied with the actual text of the module. If so, use this instead of the file contents (this is for use in an IDE where the file hasn't been saved by the user yet).

Constructors

Target 

Fields

targetId :: TargetId

module or filename

targetAllowObjCode :: Bool

object code allowed?

targetContents :: Maybe (StringBuffer, ClockTime)

in-memory text buffer?

Instances

data TargetId Source

Constructors

TargetModule ModuleName

A module name: search for the file

TargetFile FilePath (Maybe Phase)

A filename: preprocess & parse it to find the module name. If specified, the Phase indicates how to compile this file (which phase to start from). Nothing indicates the starting phase should be determined from the suffix of the filename.

setTargets :: GhcMonad m => [Target] -> m ()Source

Sets the targets for this session. Each target may be a module name or a filename. The targets correspond to the set of root modules for the program/library. Unloading the current program is achieved by setting the current set of targets to be empty, followed by load.

getTargets :: GhcMonad m => m [Target]Source

Returns the current set of targets

addTarget :: GhcMonad m => Target -> m ()Source

Add another target.

removeTarget :: GhcMonad m => TargetId -> m ()Source

Remove a target

guessTarget :: GhcMonad m => String -> Maybe Phase -> m TargetSource

Attempts to guess what Target a string refers to. This function implements the --make/GHCi command-line syntax for filenames:

  • if the string looks like a Haskell source filename, then interpret it as such
  • if adding a .hs or .lhs suffix yields the name of an existing file, then use that
  • otherwise interpret the string as a module name

Loading/compiling the program

depanalSource

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 to changes to the DynFlags to take effect you need to call this function again.

load :: GhcMonad m => LoadHowMuch -> m SuccessFlagSource

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) compilating and loading may result in files being created on disk.

Calls the reportModuleCompilationResult callback 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 callback.

loadWithLogger :: GhcMonad m => WarnErrLogger -> LoadHowMuch -> m SuccessFlagSource

Try to load the program. If a Module is supplied, then just attempt to load up to this target. If no Module is supplied, then try to load all targets.

The first argument is a function that is called after compiling each module to print wanrings and errors.

While compiling a module, all SourceErrors are caught and passed to the logger, however, this function may still throw a SourceError if dependency analysis failed (e.g., due to a parse error).

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.

type WarnErrLogger = GhcMonad m => Maybe SourceError -> m ()Source

A function called to log warnings and errors.

workingDirectoryChanged :: GhcMonad m => m ()Source

Inform GHC that the working directory has changed. GHC will flush its cache of module locations, since it may no longer be valid.

Note: Before changing the working directory make sure all threads running in the same session have stopped. If you change the working directory, you should also unload the current program (set targets to empty, followed by load).

parseModule :: GhcMonad m => ModSummary -> m ParsedModuleSource

Parse a module.

Throws a SourceError on parse error.

typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModuleSource

Typecheck and rename a parsed module.

Throws a SourceError if either fails.

desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModuleSource

Desugar a typechecked module.

loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m modSource

Load a module. Input doesn't need to be desugared.

A module must be loaded before dependent modules can be typechecked. This always includes generating a ModIface and, depending on the hscTarget, may also include code generation.

This function will always cause recompilation and will always overwrite previous compilation results (potentially files on disk).

data ParsedModule Source

The result of successful parsing.

data DesugaredModule Source

The result of successful desugaring (i.e., translation to core). Also contains all the information of a typechecked module.

coreModule :: DesugaredMod m => m -> ModGutsSource

compileToCoreModule :: GhcMonad m => FilePath -> m CoreModuleSource

This is the way to get access to the Core bindings corresponding to a module. compileToCore parses, typechecks, and desugars the module, then returns the resulting Core module (consisting of the module name, type declarations, and function declarations) if successful.

compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModuleSource

Like compileToCoreModule, but invokes the simplifier, so as to return simplified and tidied Core.

compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m ()Source

Takes a CoreModule and compiles the bindings therein to object code. The first argument is a bool flag indicating whether to run the simplifier. The resulting .o, .hi, and executable files, if any, are stored in the current directory, and named according to the module name. This has only so far been tested with a single self-contained module.

getModSummary :: GhcMonad m => ModuleName -> m ModSummarySource

Return the ModSummary of a module with the given name.

The module must be part of the module graph (see hsc_mod_graph and ModuleGraph). If this is not the case, this function will throw a GhcApiError.

This function ignores boot modules and requires that there is only one non-boot module with the given name.

Inspecting the module structure of the program

type ModuleGraph = [ModSummary]Source

A ModuleGraph contains all the nodes from the home package (only). There will be a node for each source module, plus a node for each hi-boot module.

The graph is not necessarily stored in topologically-sorted order. Use GHC.topSortModuleGraph and Digraph.flattenSCC to achieve this.

data ModSummary Source

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 :: ClockTime

Timestamp of source file

ms_obj_date :: Maybe ClockTime

Timestamp of object, if we have one

ms_srcimps :: [Located (ImportDecl RdrName)]

Source imports of the module

ms_imps :: [Located (ImportDecl RdrName)]

Non-source imports of the module

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 ModLocation Source

Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them

getModuleGraph :: GhcMonad m => m ModuleGraphSource

Get the module dependency graph.

isLoaded :: GhcMonad m => ModuleName -> m BoolSource

Return True == module is loaded.

topSortModuleGraphSource

Arguments

:: Bool

Drop hi-boot nodes? (see below)

-> [ModSummary] 
-> Maybe ModuleName

Root module name. If Nothing, use the full graph.

-> [SCC ModSummary] 

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

Inspecting modules

data ModuleInfo Source

Container for information about a Module.

getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)Source

Request information about a loaded Module

modInfoTyThings :: ModuleInfo -> [TyThing]Source

The list of top-level entities defined in a module

modInfoInstances :: ModuleInfo -> [Instance]Source

Returns the instances defined by the specified module. Warning: currently unimplemented for package modules.

lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)Source

Looks up a global name: that is, any top-level name in any visible module. Unlike lookupName, lookupGlobalName does not use the interactive context, and therefore does not require a preceding setContext.

findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]Source

Querying the environment

packageDbModulesSource

Arguments

:: GhcMonad m 
=> Bool

Only consider exposed packages.

-> m [Module] 

Return all external modules available in the package database. Modules from the current session (i.e., from the HomePackageTable) are not included.

Printing

type PrintUnqualified = (QueryQualifyName, QueryQualifyModule)Source

Interactive evaluation

getBindings :: GhcMonad m => m [TyThing]Source

Return the bindings for the current interactive session.

findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m ModuleSource

Takes a ModuleName and possibly a PackageId, and consults the filesystem and package database to find the corresponding Module, using the algorithm that is used for an import declaration.

lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m ModuleSource

Like findModule, but differs slightly when the module refers to a source file, and the file has not been loaded via load. In this case, findModule will throw an error (module not loaded), but lookupModule will check to see whether the module can also be found in a package, and if so, that package Module will be returned. If not, the usual module-not-found error will be thrown.

setContextSource

Arguments

:: GhcMonad m 
=> [Module]

entire top level scope of these modules

-> [(Module, Maybe (ImportDecl RdrName))]

exports of these modules

-> m () 

Set the interactive evaluation context.

Setting the context doesn't throw away any bindings; the bindings we've built up in the InteractiveContext simply move to the new module. They always shadow anything in scope in the current context.

getContext :: GhcMonad m => m ([Module], [(Module, Maybe (ImportDecl RdrName))])Source

Get the interactive evaluation context, consisting of a pair of the set of modules from which we take the full top-level scope, and the set of modules from which we take just the exports respectively.

getNamesInScope :: GhcMonad m => m [Name]Source

Returns all names in scope in the current interactive context

getGRE :: GhcMonad m => m GlobalRdrEnvSource

get the GlobalRdrEnv for a session

moduleIsInterpreted :: GhcMonad m => Module -> m BoolSource

Returns True if the specified module is interpreted, and hence has its full top-level scope available.

getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance]))Source

Looks up an identifier in the current interactive context (for :info) Filter the instances by the ones whose tycons (or clases resp) are in scope (qualified or otherwise). Otherwise we list a whole lot too many! The exact choice of which ones to show, and which to hide, is a judgement call. (see Trac #1581)

exprType :: GhcMonad m => String -> m TypeSource

Get the type of an expression

typeKind :: GhcMonad m => String -> m KindSource

Get the kind of a type

parseName :: GhcMonad m => String -> m [Name]Source

Parses a string as an identifier, and returns the list of Names that the identifier can refer to in the current interactive context.

data RunResult Source

Constructors

RunOk [Name]

names bound by this evaluation

RunFailed

statement failed compilation

RunException SomeException

statement raised an exception

RunBreak ThreadId [Name] (Maybe BreakInfo) 

runStmt :: GhcMonad m => String -> SingleStep -> m RunResultSource

Run a statement in the current interactive context. Statement may bind multple values.

data ModBreaks Source

All the information about the breakpoints for a given module

Constructors

ModBreaks 

Fields

modBreaks_flags :: BreakArray

The array of flags, one per breakpoint, indicating which breakpoints are enabled.

modBreaks_locs :: !(Array BreakIndex SrcSpan)

An array giving the source span of each breakpoint.

modBreaks_vars :: !(Array BreakIndex [OccName])

An array giving the names of the free variables at each breakpoint.

type BreakIndex = IntSource

Breakpoint index

lookupName :: GhcMonad m => Name -> m (Maybe TyThing)Source

Returns the TyThing for a Name. The Name may refer to any entity known to GHC, including Names defined using runStmt.

Abstract syntax elements

Packages

data PackageId Source

Essentially just a string identifying a package, including the version: e.g. parsec-1.0

Modules

data ModuleName Source

A ModuleName is essentially a simple string, e.g. Data.List.

Names

data Name Source

A unique, unambigious name for something, containing information about where that thing originated.

pprParenSymName :: NamedThing a => a -> SDocSource

print a NamedThing, adding parentheses if the name is an operator.

class NamedThing a whereSource

A class allowing convenient access to the Name of various datatypes

data RdrName Source

Do not use the data constructors of RdrName directly: prefer the family of functions that creates them, such as mkRdrUnqual

Constructors

Unqual OccName

Used for ordinary, unqualified occurrences, e.g. x, y or Foo. Create such a RdrName with mkRdrUnqual

Qual ModuleName OccName

A qualified name written by the user in source code. The module isn't necessarily the module where the thing is defined; just the one from which it is imported. Examples are Bar.x, Bar.y or Bar.Foo. Create such a RdrName with mkRdrQual

Identifiers

type Id = VarSource

isImplicitId :: Id -> BoolSource

isImplicitId tells whether an Ids info is implied by other declarations, so we don't need to put its signature in an interface file, even if it's mentioned in some other interface unfolding.

isExportedId :: Var -> BoolSource

isExportedIdVar means "don't throw this away"

idDataCon :: Id -> DataConSource

Get from either the worker or the wrapper Id to the DataCon. Currently used only in the desugarer.

INVARIANT: idDataCon (dataConWrapId d) = d: remember, dataConWrapId can return either the wrapper or the worker

isBottomingId :: Id -> BoolSource

Returns true if an application to n args would diverge

recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)Source

If the Id is that for a record selector, extract the sel_tycon and label. Panic otherwise

Type constructors

data TyCon Source

TyCons represent type constructors. Type constructors are introduced by things such as:

1) Data declarations: data Foo = ... creates the Foo type constructor of kind *

2) Type synonyms: type Foo = ... creates the Foo type constructor

3) Newtypes: newtype Foo a = MkFoo ... creates the Foo type constructor of kind * -> *

4) Class declarations: class Foo where creates the Foo type constructor of kind *

5) Type coercions! This is because we represent a coercion from t1 to t2 as a Type, where that type has kind t1 ~ t2. See Coercion for more on this

This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.

tyConDataCons :: TyCon -> [DataCon]Source

As tyConDataCons_maybe, but returns the empty list of constructors if no constructors could be found

isClassTyCon :: TyCon -> BoolSource

Is this TyCon that for a class instance?

isSynTyCon :: TyCon -> BoolSource

A product TyCon must both:

  1. Have one constructor
  2. Not be existential

However other than this there are few restrictions: they may be data or newtype TyCons of any boxity and may even be recursive.

Is this a TyCon representing a type synonym (type)?

isNewTyCon :: TyCon -> BoolSource

Is this TyCon that for a newtype

isPrimTyCon :: TyCon -> BoolSource

Does this TyCon represent something that cannot be defined in Haskell?

isFamilyTyCon :: TyCon -> BoolSource

Is this a TyCon, synonym or otherwise, that may have further instances appear?

synTyConDefn :: TyCon -> ([TyVar], Type)Source

Extract the TyVars bound by a type synonym and the corresponding (unsubstituted) right hand side. If the given TyCon is not a type synonym, panics

synTyConType :: TyCon -> TypeSource

Find the expansion of the type synonym represented by the given TyCon. The free variables of this type will typically include those TyVars bound by the TyCon. Panics if the TyCon is not that of a type synonym

synTyConResKind :: TyCon -> KindSource

Find the result Kind of a type synonym, after applying it to its arity number of type variables Actually this function works fine on data types too, but they'd always return *, so we never need to ask

Type variables

Data constructors

dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type)Source

The "signature" of the DataCon returns, in order:

1) The result of dataConAllTyVars,

2) All the ThetaTypes relating to the DataCon (coercion, dictionary, implicit parameter - whatever)

3) The type arguments to the constructor

4) The original result type of the DataCon

dataConTyCon :: DataCon -> TyConSource

The type constructor that we are building via this data constructor

dataConFieldLabels :: DataCon -> [FieldLabel]Source

The labels for the fields of this particular DataCon

dataConIsInfix :: DataCon -> BoolSource

Should the DataCon be presented infix?

isVanillaDataCon :: DataCon -> BoolSource

Vanilla DataCons are those that are nice boring Haskell 98 constructors

dataConUserType :: DataCon -> TypeSource

The user-declared type of the data constructor in the nice-to-read form:

 T :: forall a b. a -> b -> T [a]

rather than:

 T :: forall a c. forall b. (c~[a]) => a -> b -> T c

NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.

dataConStrictMarks :: DataCon -> [HsBang]Source

The strictness markings decided on by the compiler. Does not include those for existential dictionaries. The list is in one-to-one correspondence with the arity of the DataCon

Classes

Instances

Types and Kinds

data Type Source

The key representation of types within the compiler

splitForAllTys :: Type -> ([TyVar], Type)Source

Attempts to take a forall type apart, returning all the immediate such bound type variables and the remainder of the type. Always suceeds, even if that means returning an empty list of TyVars

funResultTy :: Type -> TypeSource

Extract the function result type and panic if that is not possible

type Kind = TypeSource

The key type representing kinds in the compiler. Invariant: a kind is always in one of these forms:

 FunTy k1 k2
 TyConApp PrimTyCon [...]
 TyVar kv   -- (during inference only)
 ForAll ... -- (for top-level coercions)

data PredType Source

A type of the form PredTy p represents a value whose type is the Haskell predicate p, where a predicate is what occurs before the => in a Haskell type. It can be expanded into its representation, but:

  • The type checker must treat it as opaque
  • The rest of the compiler treats it as transparent

Consider these examples:

 f :: (Eq a) => a -> Int
 g :: (?x :: Int -> Int) => a -> Int
 h :: (r\l) => {r} => {l::Int | r}

Here the Eq a and ?x :: Int -> Int and rl are all called "predicates"

type ThetaType = [PredType]Source

A collection of PredTypes

Entities

data TyThing Source

A typecheckable-thing, essentially anything that has a name

Syntax

module HsSyn

Fixities

Source locations

data SrcLoc Source

Represents a single point within a file

pprDefnLoc :: SrcSpan -> SDocSource

Pretty prints information about the SrcSpan in the style defined at ...

isGoodSrcLoc :: SrcLoc -> BoolSource

Good SrcLocs have precise information about their location

srcLocFile :: SrcLoc -> FastStringSource

Gives the filename of the SrcLoc if it is available, otherwise returns a dummy value

srcLocLine :: SrcLoc -> IntSource

Raises an error when used on a bad SrcLoc

srcLocCol :: SrcLoc -> IntSource

Raises an error when used on a bad SrcLoc

data SrcSpan Source

A SrcSpan delimits a portion of a text file. It could be represented by a pair of (line,column) coordinates, but in fact we optimise slightly by using more compact representations for single-line and zero-length spans, both of which are quite common.

The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpanSource

Create a SrcSpan between two points in a file

srcLocSpan :: SrcLoc -> SrcSpanSource

Create a SrcSpan corresponding to a single point

isGoodSrcSpan :: SrcSpan -> BoolSource

Test if a SrcSpan is good, i.e. has precise location information

srcSpanStart :: SrcSpan -> SrcLocSource

Returns the location at the start of the SrcSpan or a bad SrcSpan if that is unavailable

srcSpanEnd :: SrcSpan -> SrcLocSource

Returns the location at the end of the SrcSpan or a bad SrcSpan if that is unavailable

srcSpanStartLine :: SrcSpan -> IntSource

Raises an error when used on a bad SrcSpan

srcSpanEndLine :: SrcSpan -> IntSource

Raises an error when used on a bad SrcSpan

srcSpanStartCol :: SrcSpan -> IntSource

Raises an error when used on a bad SrcSpan

srcSpanEndCol :: SrcSpan -> IntSource

Raises an error when used on a bad SrcSpan

Located

data Located e Source

We attach SrcSpans to lots of things, so let's have a datatype for it.

Constructors

L SrcSpan e 

Instances

Constructing Located

Deconstructing Located

Combining and comparing Located values

eqLocated :: Eq a => Located a -> Located a -> BoolSource

Tests whether the two located things are equal

cmpLocated :: Ord a => Located a -> Located a -> OrderingSource

Tests the ordering of the two located things

addCLoc :: Located a -> Located b -> c -> Located cSource

Combine locations from two Located things and add them to a third thing

leftmost_largest :: SrcSpan -> SrcSpan -> OrderingSource

Alternative strategies for ordering SrcSpans

spans :: SrcSpan -> (Int, Int) -> BoolSource

Determines whether a span encloses a given line and column index

isSubspanOfSource

Arguments

:: SrcSpan

The span that may be enclosed by the other

-> SrcSpan

The span it may be enclosed by

-> Bool 

Determines whether a span is enclosed by another one

Exceptions

data GhcException Source

GHC's own exception type error messages all take the form:

	location: error

If the location is on the command line, or in GHC itself, then location=ghc. All of the error types below correspond to a location of ghc, except for ProgramError (where the string is assumed to contain a location already, so we don't print one).

Constructors

PhaseFailed String ExitCode 
Signal Int

Some other fatal signal (SIGHUP,SIGTERM)

UsageError String

Prints the short usage msg after the error

CmdLineError String

A problem with the command line arguments, but don't print usage.

Panic String

The impossible happened.

Sorry String

The user tickled something that's known not to work yet, but we're not counting it as a bug.

InstallationError String

An installation problem.

ProgramError String

An error in the user's code, probably.

showGhcException :: GhcException -> String -> StringSource

Append a description of the given exception to this string.

Token stream manipulations

getTokenStream :: GhcMonad m => Module -> m [Located Token]Source

Return module source as token stream, including comments.

The module must be in the module graph and its source must be available. Throws a SourceError on parse error.

getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]Source

Give even more information on the source than getTokenStream This function allows reconstructing the source completely with showRichTokenStream.

showRichTokenStream :: [(Located Token, String)] -> StringSource

Take a rich token stream such as produced from getRichTokenStream and return source code almost identical to the original code (except for insignificant whitespace.)

addSourceToTokens :: SrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)]Source

Given a source location and a StringBuffer corresponding to this location, return a rich token stream with the source associated to the tokens.

Miscellaneous