ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC

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.

prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a #

withSignalHandlers :: ExceptionMonad m => m a -> m a #

withCleanupSession :: GhcMonad m => m a -> m a Source #

GHC Monad

data Ghc a #

Instances

Instances details
Monad Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

return :: a -> Ghc a #

Functor Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

MonadFix Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

Applicative Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> Ghc a #

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

liftA2 :: (a -> b -> c) -> Ghc a -> Ghc b -> Ghc c #

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

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

MonadIO Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> Ghc a #

MonadThrow Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

throwM :: Exception e => e -> Ghc a #

MonadCatch Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

catch :: Exception e => Ghc a -> (e -> Ghc a) -> Ghc a #

MonadMask Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

mask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

uninterruptibleMask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

generalBracket :: Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c) #

HasDynFlags Ghc 
Instance details

Defined in GHC.Driver.Monad

GhcMonad Ghc 
Instance details

Defined in GHC.Driver.Monad

data GhcT (m :: Type -> Type) a #

Instances

Instances details
Monad m => Monad (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

return :: a -> GhcT m a #

Functor m => Functor (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Applicative m => Applicative (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> GhcT m a #

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

liftA2 :: (a -> b -> c) -> GhcT m a -> GhcT m b -> GhcT m c #

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

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

MonadIO m => MonadIO (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> GhcT m a #

MonadThrow m => MonadThrow (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

throwM :: Exception e => e -> GhcT m a #

MonadCatch m => MonadCatch (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

catch :: Exception e => GhcT m a -> (e -> GhcT m a) -> GhcT m a #

MonadMask m => MonadMask (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

mask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b #

uninterruptibleMask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b #

generalBracket :: GhcT m a -> (a -> ExitCase b -> GhcT m c) -> (a -> GhcT m b) -> GhcT m (b, c) #

MonadIO m => HasDynFlags (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

ExceptionMonad m => GhcMonad (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

getSession :: GhcT m HscEnv #

setSession :: HscEnv -> GhcT m () #

class (Functor m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where #

Methods

getSession :: m HscEnv #

setSession :: HscEnv -> m () #

Instances

Instances details
GhcMonad Ghc 
Instance details

Defined in GHC.Driver.Monad

ExceptionMonad m => GhcMonad (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

getSession :: GhcT m HscEnv #

setSession :: HscEnv -> GhcT m () #

data HscEnv #

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.

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

handleSourceError :: MonadCatch m => (SourceError -> m a) -> m a -> m a #

Flags and settings

data DynFlags #

Constructors

DynFlags 

Fields

data GeneralFlag #

Constructors

Opt_DumpToFile 
Opt_D_faststring_stats 
Opt_D_dump_minimal_imports 
Opt_DoCoreLinting 
Opt_DoLinearCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_DoAnnotationLinting 
Opt_NoLlvmMangler 
Opt_FastLlvm 
Opt_NoTypeableBinds 
Opt_WarnIsError 
Opt_ShowWarnGroups 
Opt_HideSourcePaths 
Opt_PrintExplicitForalls 
Opt_PrintExplicitKinds 
Opt_PrintExplicitCoercions 
Opt_PrintExplicitRuntimeReps 
Opt_PrintEqualityRelations 
Opt_PrintAxiomIncomps 
Opt_PrintUnicodeSyntax 
Opt_PrintExpandedSynonyms 
Opt_PrintPotentialInstances 
Opt_PrintTypecheckerElaboration 
Opt_CallArity 
Opt_Exitification 
Opt_Strictness 
Opt_LateDmdAnal 
Opt_KillAbsence 
Opt_KillOneShot 
Opt_FullLaziness 
Opt_FloatIn 
Opt_LateSpecialise 
Opt_Specialise 
Opt_SpecialiseAggressively 
Opt_CrossModuleSpecialise 
Opt_InlineGenerics 
Opt_InlineGenericsAggressively 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_StgCSE 
Opt_StgLiftLams 
Opt_LiberateCase 
Opt_SpecConstr 
Opt_SpecConstrKeen 
Opt_DoLambdaEtaExpansion 
Opt_IgnoreAsserts 
Opt_DoEtaReduction 
Opt_CaseMerge 
Opt_CaseFolding 
Opt_UnboxStrictFields 
Opt_UnboxSmallStrictFields 
Opt_DictsCheap 
Opt_EnableRewriteRules 
Opt_EnableThSpliceWarnings 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_LlvmFillUndefWithGarbage 
Opt_IrrefutableTuples 
Opt_CmmSink 
Opt_CmmStaticPred 
Opt_CmmElimCommonBlocks 
Opt_AsmShortcutting 
Opt_OmitYields 
Opt_FunToThunk 
Opt_DictsStrict 
Opt_DmdTxDictSel 
Opt_Loopification 
Opt_CfgBlocklayout 
Opt_WeightlessBlocklayout 
Opt_CprAnal 
Opt_WorkerWrapper 
Opt_SolveConstantDicts 
Opt_AlignmentSanitisation 
Opt_CatchBottoms 
Opt_NumConstantFolding 
Opt_SimplPreInlining 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_WriteInterface 
Opt_WriteHie 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_Pp 
Opt_ForceRecomp 
Opt_IgnoreOptimChanges 
Opt_IgnoreHpcChanges 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_NoHsMain 
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_GhciLeakCheck 
Opt_ValidateHie 
Opt_LocalGhciHistory 
Opt_NoIt 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_DeferTypedHoles 
Opt_DeferOutOfScopeVariables 
Opt_PIC 
Opt_PIE 
Opt_PICExecutable 
Opt_ExternalDynamicRefs 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_Hpc 
Opt_FlatCache 
Opt_ExternalInterpreter 
Opt_OptimalApplicativeDo 
Opt_VersionMacros 
Opt_WholeArchiveHsLibs 
Opt_SingleLibFolder 
Opt_KeepCAFs 
Opt_KeepGoing 
Opt_ByteCode 
Opt_LinkRts 
Opt_ErrorSpans 
Opt_DeferDiagnostics 
Opt_DiagnosticsShowCaret 
Opt_PprCaseAsLet 
Opt_PprShowTicks 
Opt_ShowHoleConstraints 
Opt_ShowValidHoleFits 
Opt_SortValidHoleFits 
Opt_SortBySizeHoleFits 
Opt_SortBySubsumHoleFits 
Opt_AbstractRefHoleFits 
Opt_UnclutterValidHoleFits 
Opt_ShowTypeAppOfHoleFits 
Opt_ShowTypeAppVarsOfHoleFits 
Opt_ShowDocsOfHoleFits 
Opt_ShowTypeOfHoleFits 
Opt_ShowProvOfHoleFits 
Opt_ShowMatchesOfHoleFits 
Opt_ShowLoadedModules 
Opt_HexWordLiterals 
Opt_SuppressCoercions 
Opt_SuppressVarKinds 
Opt_SuppressModulePrefixes 
Opt_SuppressTypeApplications 
Opt_SuppressIdInfo 
Opt_SuppressUnfoldings 
Opt_SuppressTypeSignatures 
Opt_SuppressUniques 
Opt_SuppressStgExts 
Opt_SuppressTicks 
Opt_SuppressTimestamps 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_KeepHscppFiles 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_KeepHiFiles 
Opt_KeepOFiles 
Opt_BuildDynamicToo 
Opt_DistrustAllPackages 
Opt_PackageTrust 
Opt_PluginTrustworthy 
Opt_G_NoStateHack 
Opt_G_NoOptCoercion 

data Severity #

Instances

Instances details
Show Severity 
Instance details

Defined in GHC.Types.Error

ToJson Severity 
Instance details

Defined in GHC.Types.Error

Methods

json :: Severity -> JsonDoc

data Backend #

Constructors

NCG 
LLVM 
ViaC 
Interpreter 
NoBackend 

Instances

Instances details
Eq Backend 
Instance details

Defined in GHC.Driver.Backend

Methods

(==) :: Backend -> Backend -> Bool #

(/=) :: Backend -> Backend -> Bool #

Ord Backend 
Instance details

Defined in GHC.Driver.Backend

Read Backend 
Instance details

Defined in GHC.Driver.Backend

Show Backend 
Instance details

Defined in GHC.Driver.Backend

data GhcMode #

Constructors

CompManager 
OneShot 
MkDepend 

Instances

Instances details
Eq GhcMode 
Instance details

Defined in GHC.Driver.Session

Methods

(==) :: GhcMode -> GhcMode -> Bool #

(/=) :: GhcMode -> GhcMode -> Bool #

Outputable GhcMode 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc

data GhcLink #

Instances

parseTargetFiles :: DynFlags -> [String] -> (DynFlags, [(String, Maybe Phase)], [String]) Source #

Parse command line arguments that look like files. First normalises its arguments and then splits them into source files and object files. A source file can be turned into a Target via guessTarget

setSessionDynFlags :: GhcMonad m => DynFlags -> m () 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 Bool Source #

Sets the program DynFlags. Note: this invalidates the internal cached module graph, causing more work to be done the next time load is called.

Returns a boolean indicating if preload units have changed and need to be reloaded.

setLogAction :: GhcMonad m => LogAction -> m () Source #

Set the action taken when the compiler produces a message. This can also be accomplished using setProgramDynFlags, but using setLogAction avoids invalidating the cached module graph.

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 unitState into the interactive DynFlags.

interpretPackageEnv :: DynFlags -> IO DynFlags Source #

Find the package environment (if one exists)

We interpret the package environment as a set of package flags; to be specific, if we find a package environment file like

clear-package-db
global-package-db
package-db blah/package.conf.d
package-id id1
package-id id2

we interpret this as

[ -hide-all-packages
, -clear-package-db
, -global-package-db
, -package-db blah/package.conf.d
, -package-id id1
, -package-id id2
]

There's also an older syntax alias for package-id, which is just an unadorned package id

id1
id2

Targets

data Target #

Constructors

Target 

Fields

Instances

Instances details
Outputable Target 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc

data TargetId #

Instances

Instances details
Eq TargetId 
Instance details

Defined in GHC.Types.Target

Outputable TargetId 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc

data Phase #

Instances

Instances details
Eq Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

(==) :: Phase -> Phase -> Bool #

(/=) :: Phase -> Phase -> Bool #

Show Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

Outputable Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc

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. In case of errors, just throw them.

depanalE Source #

Arguments

:: GhcMonad m 
=> [ModuleName]

excluded modules

-> Bool

allow duplicate roots

-> m (ErrorMessages, ModuleGraph) 

Perform dependency analysis like in depanal. In case of errors, the errors and an empty module graph are returned.

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

Calls the defaultWarnErrLogger after each compiling each module, whether successful or not.

If errors are encountered during dependency analysis, the module depanalE returns together with the errors an empty ModuleGraph. After processing this empty ModuleGraph, the errors of depanalE are thrown. 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 #

Constructors

IIDecl (ImportDecl GhcPs) 
IIModule ModuleName 

Instances

Instances details
Outputable InteractiveImport 
Instance details

Defined in GHC.Runtime.Context

Methods

ppr :: InteractiveImport -> SDoc

data SuccessFlag #

Constructors

Succeeded 
Failed 

Instances

Instances details
Outputable SuccessFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc

type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m () #

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 DynFlags's backend, 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.

Instances

Instances details
ParsedMod ParsedModule Source # 
Instance details

Defined in GHC

data DesugaredModule Source #

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

type TypecheckedSource = LHsBinds GhcTc Source #

type ParsedSource = Located HsModule Source #

type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) Source #

class ParsedMod m Source #

Minimal complete definition

modSummary, parsedSource

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

Instances

Instances details
Outputable CoreModule Source # 
Instance details

Defined in GHC

Methods

ppr :: CoreModule -> SDoc

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

data ModSummary #

Instances

Instances details
Outputable ModSummary 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc

data ModLocation #

Instances

Instances details
Show ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Outputable ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc

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)

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

type ModIface = ModIface_ 'ModIfaceFinal #

data ModIface_ (phase :: ModIfacePhase) #

Constructors

ModIface 

Fields

Instances

Instances details
Binary ModIface 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

put_ :: BinHandle -> ModIface -> IO ()

put :: BinHandle -> ModIface -> IO (Bin ModIface)

get :: BinHandle -> IO ModIface

(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () #

data SafeHaskellMode #

Instances

Instances details
Eq SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

Show SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

Outputable SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

Methods

ppr :: SafeHaskellMode -> SDoc

Querying the environment

Printing

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.

execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult Source #

Like execStmt, but takes a parsed statement as argument. Useful when doing preprocessing on the AST before execution, e.g. in GHCi (see GHCi.UI.runStmt).

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.

runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name] Source #

Like runDeclsWithLocation, but takes parsed declarations as argument. Useful when doing preprocessing on the AST before execution, e.g. in GHCi (see GHCi.UI.runStmt).

Get/set the current context

parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) Source #

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, Set 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], SDoc)) 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 #1581)

getNameToInstancesIndex Source #

Arguments

:: GhcMonad m 
=> [Module]

visible modules. An orphan instance will be returned if it is visible from at least one module in the list.

-> Maybe [Module]

modules to load. If this is not specified, we load modules for everything that is in scope unqualified.

-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) 

Retrieve all type and family instances in the environment, indexed by Name. Each name's lists will contain every instance in which that name is mentioned in the instance head.

Inspecting types and kinds

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

Get the type of an expression Returns the type as described by TcRnExprMode

data TcRnExprMode Source #

How should we infer a type? See Note [TcRnExprMode]

Constructors

TM_Inst

Instantiate inferred quantifiers only (:type)

TM_Default

Instantiate all quantifiers, and do eager defaulting (:type +d)

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

data HValue #

Instances

Instances details
Show HValue 
Instance details

Defined in GHCi.RemoteTypes

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

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

compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue Source #

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.

type ForeignHValue = ForeignRef HValue #

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

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

compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue Source #

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

Docs

getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)) Source #

data GetDocsFailure Source #

Failure modes for getDocs.

Constructors

NameHasNoModule Name

nameModule_maybe returned Nothing.

NoDocsInIface Module Bool

True: The module was compiled. False: The module was :loaded.

InteractiveName

The Name was defined interactively.

Instances

Instances details
Outputable GetDocsFailure Source # 
Instance details

Defined in GHC.Runtime.Eval

Methods

ppr :: GetDocsFailure -> SDoc

Other

runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a) Source #

isStmt :: ParserOpts -> String -> Bool Source #

Returns True if passed string is a statement.

hasImport :: ParserOpts -> String -> Bool Source #

Returns True if passed string has an import declaration.

isImport :: ParserOpts -> String -> Bool Source #

Returns True if passed string is an import declaration.

isDecl :: ParserOpts -> String -> Bool Source #

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

The debugger

data Resume #

Constructors

Resume 

data History #

back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) Source #

Abstract syntax elements

Units

type Unit = GenUnit UnitId #

Modules

type Module = GenModule Unit #

mkModule :: u -> ModuleName -> GenModule u #

pprModule :: Module -> SDoc #

moduleName :: GenModule unit -> ModuleName #

moduleUnit :: GenModule unit -> unit #

data ModuleName #

Instances

Instances details
Eq ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Data ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

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

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

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

NFData ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

rnf :: ModuleName -> () #

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Binary ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

put_ :: BinHandle -> ModuleName -> IO ()

put :: BinHandle -> ModuleName -> IO (Bin ModuleName)

get :: BinHandle -> IO ModuleName

Outputable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc

Names

data Name #

Instances

Instances details
Eq Name 
Instance details

Defined in GHC.Types.Name

Methods

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

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

Data Name 
Instance details

Defined in GHC.Types.Name

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Name 
Instance details

Defined in GHC.Types.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 #

NFData Name 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Binary Name 
Instance details

Defined in GHC.Types.Name

Methods

put_ :: BinHandle -> Name -> IO ()

put :: BinHandle -> Name -> IO (Bin Name)

get :: BinHandle -> IO Name

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc

NamedThing Name 
Instance details

Defined in GHC.Types.Name

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

Methods

pprBndr :: BindingSite -> Name -> SDoc

pprPrefixOcc :: Name -> SDoc

pprInfixOcc :: Name -> SDoc

bndrIsJoin_maybe :: Name -> Maybe Int

nameModule :: HasDebugCallStack => Name -> Module #

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

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

class NamedThing a where #

Minimal complete definition

getName

Methods

getOccName :: a -> OccName #

getName :: a -> Name #

Instances

Instances details
NamedThing Name 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

NamedThing Class 
Instance details

Defined in GHC.Core.Class

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

NamedThing ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getOccName :: ConLike -> OccName #

getName :: ConLike -> Name #

NamedThing PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

getOccName :: PatSyn -> OccName #

getName :: PatSyn -> Name #

NamedThing IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceDecl -> OccName #

getName :: IfaceDecl -> Name #

NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

NamedThing HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

getOccName :: HoleFitCandidate -> OccName #

getName :: HoleFitCandidate -> Name #

NamedThing IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceClassOp -> OccName #

getName :: IfaceClassOp -> Name #

NamedThing IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceConDecl -> OccName #

getName :: IfaceConDecl -> Name #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

NamedThing (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

NamedThing (HsTyVarBndr flag GhcRn) 
Instance details

Defined in GHC.Hs.Type

Methods

getOccName :: HsTyVarBndr flag GhcRn -> OccName #

getName :: HsTyVarBndr flag GhcRn -> Name #

data RdrName #

Instances

Instances details
Eq RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

Data RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

toConstr :: RdrName -> Constr #

dataTypeOf :: RdrName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Outputable RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc

HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

OutputableBndr RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

pprBndr :: BindingSite -> RdrName -> SDoc

pprPrefixOcc :: RdrName -> SDoc

pprInfixOcc :: RdrName -> SDoc

bndrIsJoin_maybe :: RdrName -> Maybe Int

DisambInfixOp RdrName 
Instance details

Defined in GHC.Parser.PostProcess

Identifiers

type Id = Var #

idType :: Id -> Kind #

recordSelectorTyCon :: Id -> RecSelParent #

Type constructors

data TyCon #

Instances

Instances details
Eq TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

Data TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

toConstr :: TyCon -> Constr #

dataTypeOf :: TyCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Uniquable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

getUnique :: TyCon -> Unique #

Outputable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

tyConArity :: TyCon -> Arity #

Type variables

type TyVar = Var #

Data constructors

data DataCon #

Instances

Instances details
Eq DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

Data DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: DataCon -> Constr #

dataTypeOf :: DataCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Outputable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

OutputableBndr DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

pprBndr :: BindingSite -> DataCon -> SDoc

pprPrefixOcc :: DataCon -> SDoc

pprInfixOcc :: DataCon -> SDoc

bndrIsJoin_maybe :: DataCon -> Maybe Int

dataConFieldLabels :: DataCon -> [FieldLabel] #

dataConSrcBangs :: DataCon -> [HsSrcBang] #

data StrictnessMark #

Instances

Instances details
Outputable StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: StrictnessMark -> SDoc

Classes

data Class #

Instances

Instances details
Eq Class 
Instance details

Defined in GHC.Core.Class

Methods

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

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

Data Class 
Instance details

Defined in GHC.Core.Class

Methods

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

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

toConstr :: Class -> Constr #

dataTypeOf :: Class -> DataType #

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

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

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

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

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

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

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

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

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

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

Uniquable Class 
Instance details

Defined in GHC.Core.Class

Methods

getUnique :: Class -> Unique #

Outputable Class 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc

NamedThing Class 
Instance details

Defined in GHC.Core.Class

classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) #

pprFundeps :: Outputable a => [FunDep a] -> SDoc #

Instances

data ClsInst #

Instances

Instances details
Data ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Methods

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

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

toConstr :: ClsInst -> Constr #

dataTypeOf :: ClsInst -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

instanceDFunId :: ClsInst -> DFunId #

pprInstance :: ClsInst -> SDoc #

pprFamInst :: FamInst -> SDoc Source #

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

data FamInst #

Instances

Instances details
Outputable FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc

NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Types and Kinds

data Type #

Instances

Instances details
Data Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc

Eq (DeBruijn Type) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn Type -> DeBruijn Type -> Bool #

(/=) :: DeBruijn Type -> DeBruijn Type -> Bool #

pprParendType :: Type -> SDoc #

pprTypeApp :: TyCon -> [Type] -> SDoc #

type Kind = Type #

type PredType = Type #

Entities

data TyThing #

Constructors

AnId Id 
AConLike ConLike 
ATyCon TyCon 
ACoAxiom (CoAxiom Branched) 

Instances

Instances details
Outputable TyThing 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc

NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

Syntax

Fixities

data FixityDirection #

Constructors

InfixL 
InfixR 
InfixN 

Instances

Instances details
Eq FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Data FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

toConstr :: FixityDirection -> Constr #

dataTypeOf :: FixityDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

put_ :: BinHandle -> FixityDirection -> IO ()

put :: BinHandle -> FixityDirection -> IO (Bin FixityDirection)

get :: BinHandle -> IO FixityDirection

Outputable FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: FixityDirection -> SDoc

defaultFixity :: Fixity #

negateFixity :: Fixity #

compareFixity :: Fixity -> Fixity -> (Bool, Bool) #

data LexicalFixity #

Constructors

Prefix 
Infix 

Instances

Instances details
Eq LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Data LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity #

toConstr :: LexicalFixity -> Constr #

dataTypeOf :: LexicalFixity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) #

gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r #

gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity #

Outputable LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: LexicalFixity -> SDoc

Source locations

data SrcLoc #

Constructors

RealSrcLoc !RealSrcLoc !(Maybe BufPos) 
UnhelpfulLoc FastString 

Instances

Instances details
Eq SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

(==) :: SrcLoc -> SrcLoc -> Bool #

(/=) :: SrcLoc -> SrcLoc -> Bool #

Show SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc

data RealSrcLoc #

Instances

Instances details
Eq RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Show RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc

mkSrcLoc :: FastString -> Int -> Int -> SrcLoc #

srcLocFile :: RealSrcLoc -> FastString #

data SrcSpan #

Constructors

RealSrcSpan !RealSrcSpan !(Maybe BufSpan) 
UnhelpfulSpan !UnhelpfulSpanReason 

Instances

Instances details
Eq SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Data SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: SrcSpan -> Constr #

dataTypeOf :: SrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () #

Binary SrcSpan 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> SrcSpan -> IO ()

put :: BinHandle -> SrcSpan -> IO (Bin SrcSpan)

get :: BinHandle -> IO SrcSpan

Outputable SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc

ToJson SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc

Binary a => Binary (Located a) 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> Located a -> IO ()

put :: BinHandle -> Located a -> IO (Bin (Located a))

get :: BinHandle -> IO (Located a)

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

data RealSrcSpan #

Instances

Instances details
Eq RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Data RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: RealSrcSpan -> Constr #

dataTypeOf :: RealSrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Show RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Binary RealSrcSpan 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> RealSrcSpan -> IO ()

put :: BinHandle -> RealSrcSpan -> IO (Bin RealSrcSpan)

get :: BinHandle -> IO RealSrcSpan

Outputable RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc

ToJson RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc

srcSpanFile :: RealSrcSpan -> FastString #

Located

data GenLocated l e #

Constructors

L l e 

Instances

Instances details
Functor (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Foldable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

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

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

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

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

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

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

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

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

null :: GenLocated l a -> Bool #

length :: GenLocated l a -> Int #

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

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

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

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

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

Traversable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

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

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

Binary a => Binary (Located a) 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> Located a -> IO ()

put :: BinHandle -> Located a -> IO (Bin (Located a))

get :: BinHandle -> IO (Located a)

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

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

Defined in GHC.Types.SrcLoc

Methods

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

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

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

Defined in GHC.Types.SrcLoc

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

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

toConstr :: GenLocated l e -> Constr #

dataTypeOf :: GenLocated l e -> DataType #

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

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (GenLocated l e)) #

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

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

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

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

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

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

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

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

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

Defined in GHC.Types.SrcLoc

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) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: GenLocated l e -> SDoc

Constructing Located

noLoc :: e -> Located e #

Deconstructing Located

getLoc :: GenLocated l e -> l #

unLoc :: GenLocated l e -> e #

Combining and comparing Located values

eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool #

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

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

Exceptions

showGhcException :: SDocContext -> GhcException -> ShowS #

newtype GhcApiError Source #

An error thrown if the GHC API is used in an incorrect fashion.

Constructors

GhcApiError String 

Instances

Instances details
Show GhcApiError Source # 
Instance details

Defined in GHC

Exception GhcApiError Source # 
Instance details

Defined in GHC

Token stream manipulations

data Token #

Instances

Instances details
Show Token 
Instance details

Defined in GHC.Parser.Lexer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Outputable Token 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc

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)

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

A pure interface to the module parser.

API Annotations

data AnnKeywordId #

Instances

Instances details
Eq AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Data AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnKeywordId -> Constr #

dataTypeOf :: AnnKeywordId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Show AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnKeywordId -> SDoc

data AnnotationComment #

Instances

Instances details
Eq AnnotationComment 
Instance details

Defined in GHC.Parser.Annotation

Data AnnotationComment 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnotationComment -> Constr #

dataTypeOf :: AnnotationComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnotationComment 
Instance details

Defined in GHC.Parser.Annotation

Show AnnotationComment 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnotationComment 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnotationComment -> SDoc

Miscellaneous