ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

GHC

Contents

Synopsis

Initialisation

defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a Source

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 => DynFlags -> m a -> m a Source

Deprecated: Cleanup is now done by runGhc/runGhcT

This function is no longer necessary, cleanup is now done by runGhc/runGhcT.

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.

Instances

Monad Ghc 

Methods

(>>=) :: Ghc a -> (a -> Ghc b) -> Ghc b Source

(>>) :: Ghc a -> Ghc b -> Ghc b Source

return :: a -> Ghc a Source

fail :: String -> Ghc a Source

Functor Ghc 

Methods

fmap :: (a -> b) -> Ghc a -> Ghc b Source

(<$) :: a -> Ghc b -> Ghc a Source

MonadFix Ghc 

Methods

mfix :: (a -> Ghc a) -> Ghc a Source

Applicative Ghc 

Methods

pure :: a -> Ghc a Source

(<*>) :: Ghc (a -> b) -> Ghc a -> Ghc b Source

(*>) :: Ghc a -> Ghc b -> Ghc b Source

(<*) :: Ghc a -> Ghc b -> Ghc a Source

MonadIO Ghc 

Methods

liftIO :: IO a -> Ghc a Source

ExceptionMonad Ghc 

Methods

gcatch :: Exception e => Ghc a -> (e -> Ghc a) -> Ghc a Source

gmask :: ((Ghc a -> Ghc a) -> Ghc b) -> Ghc b Source

gbracket :: Ghc a -> (a -> Ghc b) -> (a -> Ghc c) -> Ghc c Source

gfinally :: Ghc a -> Ghc b -> Ghc a Source

HasDynFlags Ghc 
GhcMonad Ghc 

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

(Applicative m, Monad m) => Monad (GhcT m) 

Methods

(>>=) :: GhcT m a -> (a -> GhcT m b) -> GhcT m b Source

(>>) :: GhcT m a -> GhcT m b -> GhcT m b Source

return :: a -> GhcT m a Source

fail :: String -> GhcT m a Source

Functor m => Functor (GhcT m) 

Methods

fmap :: (a -> b) -> GhcT m a -> GhcT m b Source

(<$) :: a -> GhcT m b -> GhcT m a Source

Applicative m => Applicative (GhcT m) 

Methods

pure :: a -> GhcT m a Source

(<*>) :: GhcT m (a -> b) -> GhcT m a -> GhcT m b Source

(*>) :: GhcT m a -> GhcT m b -> GhcT m b Source

(<*) :: GhcT m a -> GhcT m b -> GhcT m a Source

(Applicative m, MonadIO m) => MonadIO (GhcT m) 

Methods

liftIO :: IO a -> GhcT m a Source

ExceptionMonad m => ExceptionMonad (GhcT m) 

Methods

gcatch :: Exception e => GhcT m a -> (e -> GhcT m a) -> GhcT m a Source

gmask :: ((GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b Source

gbracket :: GhcT m a -> (a -> GhcT m b) -> (a -> GhcT m c) -> GhcT m c Source

gfinally :: GhcT m a -> GhcT m b -> GhcT m a Source

MonadIO m => HasDynFlags (GhcT m) 
ExceptionMonad m => GhcMonad (GhcT m) 

class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad m where Source

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 initGhcMonad before any call to the GHC API functions can occur.

Minimal complete definition

getSession, setSession

data HscEnv Source

HscEnv is like Session, except that some of the fields are immutable. An HscEnv is used to compile a single module from plain Haskell source code (after preprocessing) to either C, assembly or C--. Things like the module graph don't change during a single compilation.

Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.

runGhc Source

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.

runGhcT Source

Arguments

:: ExceptionMonad 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/package/ghc-paths.

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

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

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

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

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

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

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

handleSourceError Source

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.

needsTemplateHaskell :: ModuleGraph -> Bool Source

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 GeneralFlags but also a plethora of information relating to the compilation of a single file or GHC session

Constructors

DynFlags 

Fields

data GeneralFlag Source

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_DumpToFile

Append dump output to files instead of stdout.

Opt_D_faststring_stats 
Opt_D_dump_minimal_imports 
Opt_DoCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_DoAnnotationLinting 
Opt_NoLlvmMangler 
Opt_WarnIsError 
Opt_PrintExplicitForalls 
Opt_PrintExplicitKinds 
Opt_PrintExplicitCoercions 
Opt_PrintEqualityRelations 
Opt_PrintUnicodeSyntax 
Opt_PrintExpandedSynonyms 
Opt_PrintPotentialInstances 
Opt_PrintTypecheckerElaboration 
Opt_CallArity 
Opt_Strictness 
Opt_LateDmdAnal 
Opt_KillAbsence 
Opt_KillOneShot 
Opt_FullLaziness 
Opt_FloatIn 
Opt_Specialise 
Opt_SpecialiseAggressively 
Opt_CrossModuleSpecialise 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_LiberateCase 
Opt_SpecConstr 
Opt_DoLambdaEtaExpansion 
Opt_IgnoreAsserts 
Opt_DoEtaReduction 
Opt_CaseMerge 
Opt_UnboxStrictFields 
Opt_UnboxSmallStrictFields 
Opt_DictsCheap 
Opt_EnableRewriteRules 
Opt_Vectorise 
Opt_VectorisationAvoidance 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_LlvmPassVectorsInRegisters 
Opt_IrrefutableTuples 
Opt_CmmSink 
Opt_CmmElimCommonBlocks 
Opt_OmitYields 
Opt_SimpleListLiterals 
Opt_FunToThunk 
Opt_DictsStrict 
Opt_DmdTxDictSel 
Opt_Loopification 
Opt_CprAnal 
Opt_WorkerWrapper 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_WriteInterface 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_Pp 
Opt_ForceRecomp 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_NoHsMain 
Opt_SplitObjs 
Opt_SplitSections 
Opt_StgStats 
Opt_HideAllPackages 
Opt_HideAllPluginPackages 
Opt_PrintBindResult 
Opt_Haddock 
Opt_HaddockOptions 
Opt_BreakOnException 
Opt_BreakOnError 
Opt_PrintEvldWithShow 
Opt_PrintBindContents 
Opt_GenManifest 
Opt_EmbedManifest 
Opt_SharedImplib 
Opt_BuildingCabalPackage 
Opt_IgnoreDotGhci 
Opt_GhciSandbox 
Opt_GhciHistory 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_DeferTypedHoles 
Opt_PIC 
Opt_SccProfilingOn 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_Hpc 
Opt_FlatCache 
Opt_ExternalInterpreter 
Opt_SimplPreInlining 
Opt_ErrorSpans 
Opt_PprCaseAsLet 
Opt_PprShowTicks 
Opt_SuppressCoercions 
Opt_SuppressVarKinds 
Opt_SuppressModulePrefixes 
Opt_SuppressTypeApplications 
Opt_SuppressIdInfo 
Opt_SuppressUnfoldings 
Opt_SuppressTypeSignatures 
Opt_SuppressUniques 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_BuildDynamicToo 
Opt_DistrustAllPackages 
Opt_PackageTrust 

data Severity Source

Constructors

SevOutput 
SevFatal 
SevInteractive 
SevDump

Log messagse intended for compiler developers No filelinecolumn stuff

SevInfo

Log messages intended for end users. No filelinecolumn stuff.

SevWarning 
SevError

SevWarning and SevError are used for warnings and errors o The message has a filelinecolumn heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users

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:

  • 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 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 be 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.

HscInterpreted

Generate bytecode. (Requires LinkInMemory)

HscNothing

Don't generate any code. See notes above.

gopt :: GeneralFlag -> DynFlags -> Bool Source

Test whether a GeneralFlag 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)

LinkStaticLib

Link objects into a static lib

defaultObjectTarget :: Platform -> HscTarget Source

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

getSessionDynFlags :: GhcMonad m => m DynFlags Source

Grabs the DynFlags from the Session

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

Updates both the interactive and program 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.

getProgramDynFlags :: GhcMonad m => m DynFlags Source

Returns the program DynFlags.

setProgramDynFlags :: GhcMonad m => DynFlags -> m [UnitId] Source

Sets the program DynFlags.

getInteractiveDynFlags :: GhcMonad m => m DynFlags Source

Get the DynFlags used to evaluate interactive expressions.

setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () Source

Set the DynFlags used to evaluate interactive expressions. Note: this cannot be used for changes to packages. Use setSessionDynFlags, or setProgramDynFlags and then copy the pkgState into the interactive DynFlags.

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

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

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

depanal Source

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

load :: GhcMonad m => LoadHowMuch -> m SuccessFlag Source

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

Calls the defaultWarnErrLogger 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 defaultWarnErrLogger.

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.

data InteractiveImport Source

Constructors

IIDecl (ImportDecl RdrName)

Bring the exports of a particular module (filtered by an import decl) into scope

IIModule ModuleName

Bring into scope the entire top-level envt of of this module, including the things imported into it.

type WarnErrLogger = forall m. 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 ParsedModule Source

Parse a module.

Throws a SourceError on parse error.

typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule Source

Typecheck and rename a parsed module.

Throws a SourceError if either fails.

desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule Source

Desugar a typechecked module.

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

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

coreModule :: DesugaredMod m => m -> ModGuts Source

Compiling to Core

data CoreModule Source

A CoreModule consists of just the fields of a ModGuts that are needed for the compileToCoreModule interface.

Constructors

CoreModule 

Fields

compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule Source

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

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

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 topSortModuleGraph and 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

Constructors

ModSummary 

Fields

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

getModSummary :: GhcMonad m => ModuleName -> m ModSummary Source

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.

getModuleGraph :: GhcMonad m => m ModuleGraph Source

Get the module dependency graph.

isLoaded :: GhcMonad m => ModuleName -> m Bool Source

Return True == module is loaded.

topSortModuleGraph Source

Arguments

:: Bool

Drop hi-boot nodes? (see below)

-> [ModSummary] 
-> Maybe ModuleName

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

-> [SCC ModSummary] 

Topological sort of the module graph

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 -> [ClsInst] Source

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

modInfoSafe :: ModuleInfo -> SafeHaskellMode Source

Retrieve module safe haskell mode

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

data ModIface Source

A ModIface plus a ModDetails summarises everything we know about a compiled module. The ModIface is the stuff *before* linking, and can be written out to an interface file. The 'ModDetails is after linking and can be completely recovered from just the ModIface.

When we read an interface file, we also construct a ModIface from it, except that we explicitly make the mi_decls and a few other fields empty; as when reading we consolidate the declarations etc. into a number of indexed maps and environments in the ExternalPackageState.

Constructors

ModIface 

Fields

  • mi_module :: !Module

    Name of the module we are for

  • mi_sig_of :: !(Maybe Module)

    Are we a sig of another mod?

  • mi_iface_hash :: !Fingerprint

    Hash of the whole interface

  • mi_mod_hash :: !Fingerprint

    Hash of the ABI only

  • mi_flag_hash :: !Fingerprint

    Hash of the important flags used when compiling this module

  • mi_orphan :: !WhetherHasOrphans

    Whether this module has orphans

  • mi_finsts :: !WhetherHasFamInst

    Whether this module has family instances

  • mi_hsc_src :: !HscSource

    Boot? Signature?

  • mi_deps :: Dependencies

    The dependencies of the module. This is consulted for directly-imported modules, but not for anything else (hence lazy)

  • mi_usages :: [Usage]

    Usages; kept sorted so that it's easy to decide whether to write a new iface file (changing usages doesn't affect the hash of this module) NOT STRICT! we read this field lazily from the interface file It is *only* consulted by the recompilation checker

  • mi_exports :: ![IfaceExport]

    Exports Kept sorted by (mod,occ), to make version comparisons easier Records the modules that are the declaration points for things exported by this module, and the OccNames of those things

  • mi_exp_hash :: !Fingerprint

    Hash of export list

  • mi_used_th :: !Bool

    Module required TH splices when it was compiled. This disables recompilation avoidance (see #481).

  • mi_fixities :: [(OccName, Fixity)]

    Fixities NOT STRICT! we read this field lazily from the interface file

  • mi_warns :: Warnings

    Warnings NOT STRICT! we read this field lazily from the interface file

  • mi_anns :: [IfaceAnnotation]

    Annotations NOT STRICT! we read this field lazily from the interface file

  • mi_decls :: [(Fingerprint, IfaceDecl)]

    Type, class and variable declarations The hash of an Id changes if its fixity or deprecations change (as well as its type of course) Ditto data constructors, class operations, except that the hash of the parent class/tycon changes

  • mi_globals :: !(Maybe GlobalRdrEnv)

    Binds all the things defined at the top level in the original source code for this module. which is NOT the same as mi_exports, nor mi_decls (which may contains declarations for things not actually defined by the user). Used for GHCi and for inspecting the contents of modules via the GHC API only.

    (We need the source file to figure out the top-level environment, if we didn't compile this module from source then this field contains Nothing).

    Strictly speaking this field should live in the HomeModInfo, but that leads to more plumbing.

  • mi_insts :: [IfaceClsInst]

    Sorted class instance

  • mi_fam_insts :: [IfaceFamInst]

    Sorted family instances

  • mi_rules :: [IfaceRule]

    Sorted rules

  • mi_orphan_hash :: !Fingerprint

    Hash for orphan rules, class and family instances, and vectorise pragmas combined

  • mi_vect_info :: !IfaceVectInfo

    Vectorisation information

  • mi_warn_fn :: OccName -> Maybe WarningTxt

    Cached lookup for mi_warns

  • mi_fix_fn :: OccName -> Maybe Fixity

    Cached lookup for mi_fixities

  • mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)

    Cached lookup for mi_decls. The Nothing in mi_hash_fn means that the thing isn't in decls. It's useful to know that when seeing if we are up to date wrt. the old interface. The OccName is the parent of the name, if it has one.

  • mi_hpc :: !AnyHpcUsage

    True if this program uses Hpc at any point in the program.

  • mi_trust :: !IfaceTrustInfo

    Safe Haskell Trust information for this module.

  • mi_trust_pkg :: !Bool

    Do we require the package this module resides in be trusted to trust this module? This is used for the situation where a module is Safe (so doesn't require the package be trusted itself) but imports some trustworthy modules from its own package (which does require its own package be trusted). See Note [RnNames . Trust Own Package]

Querying the environment

Printing

data PrintUnqualified Source

When printing code that contains original names, we need to map the original names back to something the user understands. This is the purpose of the triple of functions that gets passed around when rendering SDoc.

Interactive evaluation

Executing statements

execStmt Source

Arguments

:: GhcMonad m 
=> String

a statement (bind or expression)

-> ExecOptions 
-> m ExecResult 

Run a statement in the current interactive context.

data ExecOptions Source

Constructors

ExecOptions 

Fields

execOptions :: ExecOptions Source

default ExecOptions

Adding new declarations

runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name] Source

Run some declarations and return any user-visible names that were brought into scope.

Get/set the current context

setContext :: GhcMonad m => [InteractiveImport] -> m () Source

Set the interactive evaluation context.

(setContext imports) sets the ic_imports field (which in turn determines what is in scope at the prompt) to imports, and constructs the ic_rn_glb_env environment to reflect it.

We retain in scope all the things defined at the prompt, and kept in ic_tythings. (Indeed, they shadow stuff from ic_imports.)

getContext :: GhcMonad m => m [InteractiveImport] 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.

setGHCiMonad :: GhcMonad m => String -> m () Source

Set the monad GHCi lifts user statements into.

Checks that a type (in string form) is an instance of the GHC.GHCi.GHCiSandboxIO type class. Sets it to be the GHCi monad if it is, throws an error otherwise.

getGHCiMonad :: GhcMonad m => m Name Source

Get the monad GHCi lifts user statements into.

Inspecting the current context

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

Return the bindings for the current interactive session.

getInsts :: GhcMonad m => m ([ClsInst], [FamInst]) Source

Return the instances for the current interactive session.

findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module Source

Takes a ModuleName and possibly a UnitId, 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 Module Source

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.

isModuleTrusted :: GhcMonad m => Module -> m Bool Source

Check that a module is safe to import (according to Safe Haskell).

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

moduleTrustReqs :: GhcMonad m => Module -> m (Bool, [UnitId]) Source

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

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

Returns all names in scope in the current interactive context

getRdrNamesInScope :: GhcMonad m => m [RdrName] Source

Returns all RdrNames in scope in the current interactive context, excluding any that are internally-generated.

getGRE :: GhcMonad m => m GlobalRdrEnv Source

get the GlobalRdrEnv for a session

moduleIsInterpreted :: GhcMonad m => Module -> m Bool Source

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

getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst])) 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)

Inspecting types and kinds

exprType :: GhcMonad m => String -> m Type Source

Get the type of an expression Returns its most general type

typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind) Source

Get the kind of a type

Looking up a Name

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.

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.

Compiling expressions

parseExpr :: GhcMonad m => String -> m (LHsExpr RdrName) Source

Parse an expression, the parsed expression can be further processed and passed to compileParsedExpr.

compileExpr :: GhcMonad m => String -> m HValue Source

Compile an expression, run it and deliver the resulting HValue.

dynCompileExpr :: GhcMonad m => String -> m Dynamic Source

Compile an expression, run it and return the result as a Dynamic.

compileExprRemote :: GhcMonad m => String -> m ForeignHValue Source

Compile an expression, run it and deliver the resulting HValue.

compileParsedExprRemote :: GhcMonad m => LHsExpr RdrName -> m ForeignHValue Source

Compile an parsed expression (before renaming), run it and deliver the resulting HValue.

Other

isStmt :: DynFlags -> String -> Bool Source

Returns True if passed string is a statement.

hasImport :: DynFlags -> String -> Bool Source

Returns True if passed string has an import declaration.

isImport :: DynFlags -> String -> Bool Source

Returns True if passed string is an import declaration.

isDecl :: DynFlags -> String -> Bool Source

Returns True if passed string is a declaration but not a splice.

The debugger

data ModBreaks Source

All the information about the breakpoints for a module

Constructors

ModBreaks 

Fields

type BreakIndex = Int Source

Breakpoint index

Deprecated API

data RunResult Source

The type returned by the deprecated runStmt and runStmtWithLocation API

Constructors

RunOk [Name]

names bound by this evaluation

RunException SomeException

statement raised an exception

RunBreak ThreadId [Name] (Maybe BreakInfo) 

runStmt :: GhcMonad m => String -> SingleStep -> m RunResult Source

Deprecated: use execStmt

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

runStmtWithLocation :: GhcMonad m => String -> Int -> String -> SingleStep -> m RunResult Source

Deprecated: use execStmtWithLocation

Abstract syntax elements

Packages

data UnitId Source

A string which uniquely identifies a package. For wired-in packages, it is just the package name, but for user compiled packages, it is a hash. ToDo: when the key is a hash, we can do more clever things than store the hex representation and hash-cons those strings.

Instances

Eq UnitId 

Methods

(==) :: UnitId -> UnitId -> Bool

(/=) :: UnitId -> UnitId -> Bool

Data UnitId 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId Source

toConstr :: UnitId -> Constr Source

dataTypeOf :: UnitId -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) Source

gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r Source

gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

Ord UnitId 
BinaryStringRep UnitId 
Outputable UnitId 
Uniquable UnitId 
Binary UnitId 

Modules

data Module Source

A Module is a pair of a UnitId and a ModuleName.

Instances

Eq Module 

Methods

(==) :: Module -> Module -> Bool

(/=) :: Module -> Module -> Bool

Data Module 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module Source

toConstr :: Module -> Constr Source

dataTypeOf :: Module -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Module) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) Source

gmapT :: (forall b. Data b => b -> b) -> Module -> Module Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source

Ord Module 
Outputable Module 
Uniquable Module 
Binary Module 

data ModuleName Source

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

Instances

Eq ModuleName 
Data ModuleName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName Source

toConstr :: ModuleName -> Constr Source

dataTypeOf :: ModuleName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) Source

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName Source

Ord ModuleName 
BinaryStringRep ModuleName 
Outputable ModuleName 
Uniquable ModuleName 
Binary ModuleName 

Names

data Name Source

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

Instances

Eq Name 

Methods

(==) :: Name -> Name -> Bool

(/=) :: Name -> Name -> Bool

Data Name 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name Source

toConstr :: Name -> Constr Source

dataTypeOf :: Name -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Name) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) Source

gmapT :: (forall b. Data b => b -> b) -> Name -> Name Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source

Ord Name 

Methods

compare :: Name -> Name -> Ordering

(<) :: Name -> Name -> Bool

(<=) :: Name -> Name -> Bool

(>) :: Name -> Name -> Bool

(>=) :: Name -> Name -> Bool

max :: Name -> Name -> Name

min :: Name -> Name -> Name

OutputableBndr Name 
Outputable Name 
Uniquable Name 
Binary Name 
HasOccName Name 

Methods

occName :: Name -> OccName Source

NamedThing Name 
type PostRn Name ty = ty 
type PostTc Name ty = PlaceHolder 

pprParenSymName :: NamedThing a => a -> SDoc Source

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

data RdrName Source

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

  • Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar`
( ~ )

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

Instances

Eq RdrName 

Methods

(==) :: RdrName -> RdrName -> Bool

(/=) :: RdrName -> RdrName -> Bool

Data RdrName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName Source

toConstr :: RdrName -> Constr Source

dataTypeOf :: RdrName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) Source

gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source

Ord RdrName 
OutputableBndr RdrName 
Outputable RdrName 
HasOccName RdrName 
type PostRn RdrName ty = PlaceHolder 
type PostTc RdrName ty = PlaceHolder 

Identifiers

type Id = Var Source

isImplicitId :: Id -> Bool Source

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

isExportedIdVar means "don't throw this away"

idDataCon :: Id -> DataCon Source

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

Returns true if an application to n args would diverge

recordSelectorTyCon :: Id -> RecSelParent Source

If the Id is that for a record selector, extract the sel_tycon. 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 *

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

Instances

Eq TyCon 

Methods

(==) :: TyCon -> TyCon -> Bool

(/=) :: TyCon -> TyCon -> Bool

Data TyCon 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCon -> c TyCon Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon Source

toConstr :: TyCon -> Constr Source

dataTypeOf :: TyCon -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCon) Source

gmapT :: (forall b. Data b => b -> b) -> TyCon -> TyCon Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TyCon -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCon -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source

Ord TyCon 

Methods

compare :: TyCon -> TyCon -> Ordering

(<) :: TyCon -> TyCon -> Bool

(<=) :: TyCon -> TyCon -> Bool

(>) :: TyCon -> TyCon -> Bool

(>=) :: TyCon -> TyCon -> Bool

max :: TyCon -> TyCon -> TyCon

min :: TyCon -> TyCon -> TyCon

Outputable TyCon 
Uniquable TyCon 
NamedThing TyCon 

tyConTyVars :: TyCon -> [TyVar] Source

The kind and type variables used in the type constructor. Invariant: length tyvars = arity Precisely, this list scopes over:

  1. The algTcStupidTheta
  2. The cached types in algTyConRhs.NewTyCon
  3. The family instance types if present

Note that it does not scope over the data constructors.

tyConDataCons :: TyCon -> [DataCon] Source

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

tyConArity :: TyCon -> Arity Source

Number of arguments this TyCon must receive to be considered saturated (including implicit kind variables)

isClassTyCon :: TyCon -> Bool Source

Is this TyCon that for a class instance?

isTypeSynonymTyCon :: TyCon -> Bool Source

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

isTypeFamilyTyCon :: TyCon -> Bool Source

Is this a synonym TyCon that can have may have further instances appear?

isNewTyCon :: TyCon -> Bool Source

Is this TyCon that for a newtype

isPrimTyCon :: TyCon -> Bool Source

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

isFamilyTyCon :: TyCon -> Bool Source

Is this a TyCon, synonym or otherwise, that defines a family?

isOpenFamilyTyCon :: TyCon -> Bool Source

Is this a TyCon, synonym or otherwise, that defines a family with instances?

isOpenTypeFamilyTyCon :: TyCon -> Bool Source

Is this an open type family TyCon?

tyConClass_maybe :: TyCon -> Maybe Class Source

If this TyCon is that for a class instance, return the class it is for. Otherwise returns Nothing

synTyConRhs_maybe :: TyCon -> Maybe Type Source

Extract the information pertaining to the right hand side of a type synonym (type) declaration.

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

Extract the TyVars bound by a vanilla type synonym and the corresponding (unsubstituted) right hand side.

tyConKind :: TyCon -> Kind Source

Kind of this TyCon (full kind, not just the return kind)

Type variables

Data constructors

data DataCon Source

A data constructor

Instances

Eq DataCon 

Methods

(==) :: DataCon -> DataCon -> Bool

(/=) :: DataCon -> DataCon -> Bool

Data DataCon 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon Source

toConstr :: DataCon -> Constr Source

dataTypeOf :: DataCon -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) Source

gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source

gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

Ord DataCon 
OutputableBndr DataCon 
Outputable DataCon 
Uniquable DataCon 
NamedThing DataCon 

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

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

Should the DataCon be presented infix?

isVanillaDataCon :: DataCon -> Bool Source

Vanilla DataCons are those that are nice boring Haskell 98 constructors

dataConUserType :: DataCon -> Type Source

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.

dataConSrcBangs :: DataCon -> [HsSrcBang] Source

Strictness/unpack annotations, from user; or, for imported DataCons, from the interface file The list is in one-to-one correspondence with the arity of the DataCon

Classes

data Class Source

Instances

Eq Class 

Methods

(==) :: Class -> Class -> Bool

(/=) :: Class -> Class -> Bool

Data Class 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class Source

toConstr :: Class -> Constr Source

dataTypeOf :: Class -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Class) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) Source

gmapT :: (forall b. Data b => b -> b) -> Class -> Class Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source

Ord Class 

Methods

compare :: Class -> Class -> Ordering

(<) :: Class -> Class -> Bool

(<=) :: Class -> Class -> Bool

(>) :: Class -> Class -> Bool

(>=) :: Class -> Class -> Bool

max :: Class -> Class -> Class

min :: Class -> Class -> Class

Outputable Class 
Uniquable Class 
NamedThing Class 

Instances

data ClsInst Source

Instances

Data ClsInst 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst Source

toConstr :: ClsInst -> Constr Source

dataTypeOf :: ClsInst -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) Source

gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source

Outputable ClsInst 
NamedThing ClsInst 

pprFamInst :: FamInst -> SDoc Source

Pretty-prints a FamInst (type/data family instance) with its defining location.

Types and Kinds

data Type Source

The key representation of types within the compiler

Instances

Data Type 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type Source

toConstr :: Type -> Constr Source

dataTypeOf :: Type -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Type) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) Source

gmapT :: (forall b. Data b => b -> b) -> Type -> Type Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source

Outputable Type 

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

Take a ForAllTy apart, returning the list of tyvars and the result type. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.

funResultTy :: Type -> Type Source

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

type Kind = Type Source

The key type representing kinds in the compiler.

type PredType = Type Source

A type of the form p of kind Constraint represents a value whose type is the Haskell predicate p, where a predicate is what occurs before the => in a Haskell type.

We use PredType as documentation to mark those types that we guarantee to have this kind.

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

pprForAll :: [TyBinder] -> SDoc Source

Render the "forall ... ." or "forall ... ->" bit of a type. Do not pass in anonymous binders!

Entities

data TyThing Source

A global typecheckable-thing, essentially anything that has a name. Not to be confused with a TcTyThing, which is also a typecheckable thing but in the *local* context. See TcEnv for how to retrieve a TyThing given a Name.

Syntax

module HsSyn

Fixities

data FixityDirection Source

Constructors

InfixL 
InfixR 
InfixN 

Instances

Eq FixityDirection 
Data FixityDirection 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection Source

toConstr :: FixityDirection -> Constr Source

dataTypeOf :: FixityDirection -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) Source

gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

Outputable FixityDirection 
Binary FixityDirection 

Source locations

noSrcLoc :: SrcLoc Source

Built-in "bad" SrcLoc values for particular locations

srcLocFile :: RealSrcLoc -> FastString Source

Gives the filename of the RealSrcLoc

srcLocLine :: RealSrcLoc -> Int Source

Raises an error when used on a "bad" SrcLoc

srcLocCol :: RealSrcLoc -> Int Source

Raises an error when used on a "bad" SrcLoc

data SrcSpan Source

A SrcSpan identifies either a specific portion of a text file or a human-readable description of a location.

Instances

Eq SrcSpan 

Methods

(==) :: SrcSpan -> SrcSpan -> Bool

(/=) :: SrcSpan -> SrcSpan -> Bool

Data SrcSpan 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan Source

toConstr :: SrcSpan -> Constr Source

dataTypeOf :: SrcSpan -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) Source

gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan Source

Ord SrcSpan 
Show SrcSpan 
Outputable SrcSpan 
Binary SrcSpan 
Binary a => Binary (GenLocated SrcSpan a) 

data RealSrcSpan Source

A RealSrcSpan 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.

Instances

Eq RealSrcSpan 
Data RealSrcSpan 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RealSrcSpan -> c RealSrcSpan Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RealSrcSpan Source

toConstr :: RealSrcSpan -> Constr Source

dataTypeOf :: RealSrcSpan -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c RealSrcSpan) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RealSrcSpan) Source

gmapT :: (forall b. Data b => b -> b) -> RealSrcSpan -> RealSrcSpan Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r Source

gmapQ :: (forall d. Data d => d -> u) -> RealSrcSpan -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> RealSrcSpan -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan Source

Ord RealSrcSpan 
Show RealSrcSpan 
Outputable RealSrcSpan 

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan Source

Create a SrcSpan between two points in a file

srcLocSpan :: SrcLoc -> SrcSpan Source

Create a SrcSpan corresponding to a single point

isGoodSrcSpan :: SrcSpan -> Bool Source

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

noSrcSpan :: SrcSpan Source

Built-in "bad" SrcSpans for common sources of location uncertainty

srcSpanStart :: SrcSpan -> SrcLoc Source

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

srcSpanEnd :: SrcSpan -> SrcLoc Source

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

Located

data GenLocated l e Source

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

Constructors

L l e 

Instances

Functor (GenLocated l) 

Methods

fmap :: (a -> b) -> GenLocated l a -> GenLocated l b Source

(<$) :: a -> GenLocated l b -> GenLocated l a Source

Foldable (GenLocated l) 

Methods

fold :: Monoid m => GenLocated l m -> m Source

foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m Source

foldr :: (a -> b -> b) -> b -> GenLocated l a -> b Source

foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b Source

foldl :: (b -> a -> b) -> b -> GenLocated l a -> b Source

foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b Source

foldr1 :: (a -> a -> a) -> GenLocated l a -> a Source

foldl1 :: (a -> a -> a) -> GenLocated l a -> a Source

toList :: GenLocated l a -> [a] Source

null :: GenLocated l a -> Bool Source

length :: GenLocated l a -> Int Source

elem :: Eq a => a -> GenLocated l a -> Bool Source

maximum :: Ord a => GenLocated l a -> a Source

minimum :: Ord a => GenLocated l a -> a Source

sum :: Num a => GenLocated l a -> a Source

product :: Num a => GenLocated l a -> a Source

Traversable (GenLocated l) 

Methods

traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) Source

sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) Source

mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) Source

sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) Source

(Eq l, Eq e) => Eq (GenLocated l e) 

Methods

(==) :: GenLocated l e -> GenLocated l e -> Bool

(/=) :: GenLocated l e -> GenLocated l e -> Bool

(Data l, Data e) => Data (GenLocated l e) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) Source

toConstr :: GenLocated l e -> Constr Source

dataTypeOf :: GenLocated l e -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (GenLocated l e)) Source

gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r Source

gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) Source

(Ord l, Ord e) => Ord (GenLocated l e) 

Methods

compare :: GenLocated l e -> GenLocated l e -> Ordering

(<) :: GenLocated l e -> GenLocated l e -> Bool

(<=) :: GenLocated l e -> GenLocated l e -> Bool

(>) :: GenLocated l e -> GenLocated l e -> Bool

(>=) :: GenLocated l e -> GenLocated l e -> Bool

max :: GenLocated l e -> GenLocated l e -> GenLocated l e

min :: GenLocated l e -> GenLocated l e -> GenLocated l e

(Outputable l, Outputable e) => Outputable (GenLocated l e) 
Binary a => Binary (GenLocated SrcSpan a) 

Constructing Located

noLoc :: e -> Located e Source

Deconstructing Located

unLoc :: GenLocated l e -> e Source

Combining and comparing Located values

eqLocated :: Eq a => Located a -> Located a -> Bool Source

Tests whether the two located things are equal

cmpLocated :: Ord a => Located a -> Located a -> Ordering Source

Tests the ordering of the two located things

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

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

leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering Source

Alternative strategies for ordering SrcSpans

leftmost_largest :: SrcSpan -> SrcSpan -> Ordering Source

Alternative strategies for ordering SrcSpans

rightmost :: SrcSpan -> SrcSpan -> Ordering Source

Alternative strategies for ordering SrcSpans

spans :: SrcSpan -> (Int, Int) -> Bool Source

Determines whether a span encloses a given line and column index

isSubspanOf Source

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

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.

PprPanic String SDoc 
Sorry String

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

PprSorry String SDoc 
InstallationError String

An installation problem.

ProgramError String

An error in the user's code, probably.

PprProgramError String SDoc 

showGhcException :: GhcException -> String -> String Source

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)] -> String Source

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 :: RealSrcLoc -> 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.

Pure interface to the parser

parser Source

Arguments

:: String

Haskell module source text (full Unicode is supported)

-> DynFlags

the flags

-> FilePath

the filename (for source locations)

-> Either ErrorMessages (WarningMessages, Located (HsModule RdrName)) 

A pure interface to the module parser.

API Annotations

data AnnKeywordId Source

API Annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not captured in the existing AST.

The annotations, together with original source comments are made available in the pm_annotations field of ParsedModule. Comments are only retained if Opt_KeepRawTokenStream is set in DynFlags before parsing.

The wiki page describing this feature is https://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations

Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [Api annotations] above for details of the usage

Constructors

AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseC

'}'

AnnCloseP

')'

AnnCloseS

']'

AnnColon 
AnnComma

as a list separator

AnnCommaTuple

in a RdrName for a tuple

AnnDarrow

'=>'

AnnDarrowU

'=>', unicode variant

AnnData 
AnnDcolon

'::'

AnnDcolonU

'::', unicode variant

AnnDefault 
AnnDeriving 
AnnDo 
AnnDot

.

AnnDotdot

'..'

AnnElse 
AnnEqual 
AnnExport 
AnnFamily 
AnnForall 
AnnForallU

Unicode variant

AnnForeign 
AnnFunId

for function name in matches where there are multiple equations for the function.

AnnGroup 
AnnHeader

for CType

AnnHiding 
AnnIf 
AnnImport 
AnnIn 
AnnInfix

'infix' or 'infixl' or 'infixr'

AnnInstance 
AnnLam 
AnnLarrow

'<-'

AnnLarrowU

'<-', unicode variant

AnnLet 
AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnName

where a name loses its location in the AST, this carries it

AnnOf 
AnnOpen

'(#' or '{-# LANGUAGE' etc

AnnOpenC

'{'

AnnOpenE

'[e|' or '[e||'

AnnOpenP

'('

AnnOpenPE

'$('

AnnOpenPTE

'$$('

AnnOpenS

'['

AnnPackageName 
AnnPattern 
AnnProc 
AnnQualified 
AnnRarrow

'->'

AnnRarrowU

'->', unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnStatic

static

AnnThen 
AnnThIdSplice

$

AnnThIdTySplice

$$

AnnThTyQuote

double '''

AnnTilde

'~'

AnnTildehsh

~#

AnnType 
AnnUnit

'()' for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

'->'

AnnrarrowtailU

'->', unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

AnnEofPos 

Instances

Eq AnnKeywordId 
Data AnnKeywordId 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnKeywordId -> c AnnKeywordId Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnKeywordId Source

toConstr :: AnnKeywordId -> Constr Source

dataTypeOf :: AnnKeywordId -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c AnnKeywordId) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnKeywordId) Source

gmapT :: (forall b. Data b => b -> b) -> AnnKeywordId -> AnnKeywordId Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r Source

gmapQ :: (forall d. Data d => d -> u) -> AnnKeywordId -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnKeywordId -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source

Ord AnnKeywordId 
Show AnnKeywordId 
Outputable AnnKeywordId 

data AnnotationComment Source

Constructors

AnnDocCommentNext String

something beginning '-- |'

AnnDocCommentPrev String

something beginning '-- ^'

AnnDocCommentNamed String

something beginning '-- $'

AnnDocSection Int String

a section heading

AnnDocOptions String

doc options (prune, ignore-exports, etc)

AnnDocOptionsOld String

doc options declared "-- # ..."-style

AnnLineComment String

comment starting by "--"

AnnBlockComment String

comment in {- -}

Instances

Eq AnnotationComment 
Data AnnotationComment 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnotationComment -> c AnnotationComment Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationComment Source

toConstr :: AnnotationComment -> Constr Source

dataTypeOf :: AnnotationComment -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationComment) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationComment) Source

gmapT :: (forall b. Data b => b -> b) -> AnnotationComment -> AnnotationComment Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r Source

gmapQ :: (forall d. Data d => d -> u) -> AnnotationComment -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationComment -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source

Ord AnnotationComment 
Show AnnotationComment 
Outputable AnnotationComment 

getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] Source

Retrieve a list of annotation SrcSpans based on the SrcSpan of the annotated AST element, and the known type of the annotation.

getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) Source

Retrieve a list of annotation SrcSpans based on the SrcSpan of the annotated AST element, and the known type of the annotation. The list is removed from the annotations.

getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment] Source

Retrieve the comments allocated to the current SrcSpan

Note: A given SrcSpan may appear in multiple AST elements, beware of duplicates

getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns) Source

Retrieve the comments allocated to the current SrcSpan, and remove them from the annotations

unicodeAnn :: AnnKeywordId -> AnnKeywordId Source

Convert a normal annotation into its unicode equivalent one

Miscellaneous