ghc-9.2.4: The GHC API
Safe HaskellSafe-Inferred
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.

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

Temporarily install standard signal handlers for catching ^C, which just throw an exception in the current thread.

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

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

Instances details
MonadFix Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

MonadIO Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> Ghc a Source #

Applicative Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> Ghc a Source #

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

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

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

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

Functor Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Monad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

return :: a -> Ghc a Source #

MonadCatch Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

MonadMask Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

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

MonadThrow Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

GhcMonad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

HasDynFlags Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

HasLogger Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

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

Instances details
MonadIO m => MonadIO (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> GhcT m a Source #

Applicative m => Applicative (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> GhcT m a Source #

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

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

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

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

Functor m => Functor (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Monad m => Monad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

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 #

MonadCatch m => MonadCatch (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

MonadMask m => MonadMask (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

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

MonadThrow m => MonadThrow (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

ExceptionMonad m => GhcMonad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

MonadIO m => HasDynFlags (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

MonadIO m => HasLogger (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger 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.

Instances

Instances details
GhcMonad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

ExceptionMonad m => GhcMonad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

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--. It's also used to store the dynamic linker state to allow for multiple linkers in the same address space. 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.

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

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

handleSourceError Source #

Arguments

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

needsTemplateHaskellOrQQ :: ModuleGraph -> Bool Source #

Determines whether a set of modules requires Template Haskell or Quasi Quotes

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_DoLinearCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_DoAnnotationLinting 
Opt_DoBoundsChecking 
Opt_NoLlvmMangler 
Opt_FastLlvm 
Opt_NoTypeableBinds 
Opt_DistinctConstructorTables 
Opt_InfoTableMap 
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

deprecated, no effect and behaviour is now default. Allowed switching of a special demand transformer for dictionary selectors

Opt_Loopification 
Opt_CfgBlocklayout

Use the cfg based block layout algorithm.

Opt_WeightlessBlocklayout

Layout based on last instruction per block.

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
-fPIC
Opt_PIE
-fPIE
Opt_PICExecutable
-pie
Opt_ExternalDynamicRefs 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_CompactUnwind
-fcompact-unwind
Opt_Hpc 
Opt_FamAppCache 
Opt_ExternalInterpreter 
Opt_OptimalApplicativeDo 
Opt_VersionMacros 
Opt_WholeArchiveHsLibs 
Opt_SingleLibFolder 
Opt_ExposeInternalSymbols 
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

Suppress timestamps in dumps

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

Constructors

SevOutput 
SevFatal 
SevInteractive 
SevDump

Log message intended for compiler developers No file/line/column stuff

SevInfo

Log messages intended for end users. No file/line/column stuff.

SevWarning 
SevError

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

Instances

Instances details
Show Severity Source # 
Instance details

Defined in GHC.Types.Error

ToJson Severity Source # 
Instance details

Defined in GHC.Types.Error

Eq Severity Source # 
Instance details

Defined in GHC.Types.Error

data Backend Source #

Code generation backends.

GHC supports several code generation backends serving different purposes (producing machine code, producing ByteCode for the interpreter) and supporting different platforms.

Constructors

NCG

Native code generator backend.

Compiles Cmm code into textual assembler, then relies on an external assembler toolchain to produce machine code.

Only supports a few platforms (X86, PowerPC, SPARC).

See GHC.CmmToAsm.

LLVM

LLVM backend.

Compiles Cmm code into LLVM textual IR, then relies on LLVM toolchain to produce machine code.

It relies on LLVM support for the calling convention used by the NCG backend to produce code objects ABI compatible with it (see "cc 10" or "ghccc" calling convention in https://llvm.org/docs/LangRef.html#calling-conventions).

Support a few platforms (X86, AArch64, s390x, ARM).

See GHC.CmmToLlvm

ViaC

Via-C backend.

Compiles Cmm code into C code, then relies on a C compiler to produce machine code.

It produces code objects that are *not* ABI compatible with those produced by NCG and LLVM backends.

Produced code is expected to be less efficient than the one produced by NCG and LLVM backends because STG registers are not pinned into real registers. On the other hand, it supports more target platforms (those having a valid C toolchain).

See GHC.CmmToC

Interpreter

ByteCode interpreter.

Produce ByteCode objects (BCO, see GHC.ByteCode) that can be interpreted. It is used by GHCi.

Currently some extensions are not supported (foreign primops).

See GHC.StgToByteCode

NoBackend

No code generated.

Use this to disable code generation. It is particularly useful when GHC is used as a library for other purpose than generating code (e.g. to generate documentation with Haddock) or when the user requested it (via -fno-code) for some reason.

Instances

Instances details
Read Backend Source # 
Instance details

Defined in GHC.Driver.Backend

Show Backend Source # 
Instance details

Defined in GHC.Driver.Backend

Eq Backend Source # 
Instance details

Defined in GHC.Driver.Backend

Methods

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

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

Ord Backend Source # 
Instance details

Defined in GHC.Driver.Backend

gopt :: GeneralFlag -> DynFlags -> Bool Source #

Test whether a GeneralFlag is set

Note that dynamicNow (i.e., dynamic objects built with `-dynamic-too`) always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables Opt_SplitSections.

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 GHC.Unit.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 GHC.Unit.Finder for why we need this

Instances

Instances details
Outputable GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc Source #

Eq GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Methods

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

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

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

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

getSessionDynFlags :: GhcMonad m => m DynFlags Source #

Grabs the DynFlags from the Session

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

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.

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. Also initialise (load) plugins.

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

interpretPackageEnv :: Logger -> 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

Logging

pushLogHook :: (LogAction -> LogAction) -> Logger -> Logger Source #

Push a log hook

popLogHook :: Logger -> Logger Source #

Pop a log hook

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

Push a log hook on the stack

popLogHookM :: GhcMonad m => m () Source #

Pop a log hook from the stack

modifyLogger :: GhcMonad m => (Logger -> Logger) -> m () Source #

Modify the logger

putMsgM :: GhcMonad m => SDoc -> m () Source #

Put a log message

putLogMsgM :: GhcMonad m => WarnReason -> Severity -> SrcSpan -> SDoc -> m () Source #

Put a log message

Targets

data Target Source #

A compilation target.

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

Constructors

Target 

Fields

  • targetId :: !TargetId

    module or filename

  • targetAllowObjCode :: !Bool

    object code allowed?

  • targetContents :: !(Maybe (InputFileBuffer, UTCTime))

    Optional in-memory buffer containing the source code GHC should use for this target instead of reading it from disk.

    Since GHC version 8.10 modules which require preprocessors such as Literate Haskell or CPP to run are also supported.

    If a corresponding source file does not exist on disk this will result in a SourceError exception if targetId = TargetModule _ is used. However together with targetId = TargetFile _ GHC will not complain about the file missing.

Instances

Instances details
Outputable Target Source # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc Source #

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.

Instances

Instances details
Outputable TargetId Source # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc Source #

Eq TargetId Source # 
Instance details

Defined in GHC.Types.Target

data Phase Source #

Instances

Instances details
Show Phase Source # 
Instance details

Defined in GHC.Driver.Phases

Outputable Phase Source # 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc Source #

Eq Phase Source # 
Instance details

Defined in GHC.Driver.Phases

Methods

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

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

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

Constructors

IIDecl (ImportDecl GhcPs)

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.

Instances

Instances details
Outputable InteractiveImport Source # 
Instance details

Defined in GHC.Runtime.Context

data SuccessFlag Source #

Constructors

Succeeded 
Failed 

Instances

Instances details
Outputable SuccessFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc Source #

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

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

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

A 'ModuleGraph' contains all the nodes from the home package (only). See 'ModuleGraphNode' for information about the nodes.

Modules need to be compiled. hs-boots need to be typechecked before the associated "real" module so modules with {-# SOURCE #-} imports can be built. Instantiations also need to be typechecked to ensure that the module fits the signature. Substantiation typechecking is roughly comparable to the check that the module and its hs-boot agree.

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

mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph Source #

Map a function f over all the ModSummaries. To preserve invariants f can't change the isBoot status.

mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary Source #

Look up a ModSummary in the ModuleGraph

data ModSummary Source #

Data for a module node in a ModuleGraph. Module nodes of the module graph are one of:

  • A regular Haskell source module
  • A hi-boot source module

Constructors

ModSummary 

Fields

Instances

Instances details
Outputable ModSummary Source # 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc Source #

data ModLocation Source #

Module Location

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

For a module in another unit, the ml_hs_file and ml_obj_file components of ModLocation are undefined.

The locations specified by a ModLocation may or may not correspond to actual files yet: for example, even if the object file doesn't exist, the ModLocation still contains the path to where the object file will reside if/when it is created.

Constructors

ModLocation 

Fields

  • ml_hs_file :: Maybe FilePath

    The source file, if we have one. Package modules probably don't have source files.

  • ml_hi_file :: FilePath

    Where the .hi file is, whether or not it exists yet. Always of form foo.hi, even if there is an hi-boot file (we add the -boot suffix later)

  • ml_obj_file :: FilePath

    Where the .o file is, whether or not it exists yet. (might not exist either because the module hasn't been compiled yet, or because it is part of a unit with a .a file)

  • ml_hie_file :: FilePath

    Where the .hie file is, whether or not it exists yet.

Instances

Instances details
Show ModLocation Source # 
Instance details

Defined in GHC.Unit.Module.Location

Outputable ModLocation Source # 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc Source #

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

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

data ModIface_ (phase :: ModIfacePhase) 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_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_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 :: [IfaceDeclExts phase]

    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_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 [Trust Own Package] in GHC.Rename.Names

  • mi_complete_matches :: [IfaceCompleteMatch]
     
  • mi_doc_hdr :: Maybe HsDocString

    Module header.

  • mi_decl_docs :: DeclDocMap

    Docs on declarations.

  • mi_arg_docs :: ArgDocMap

    Docs on arguments.

  • mi_final_exts :: !(IfaceBackendExts phase)

    Either () or ModIfaceBackend for a fully instantiated interface.

  • mi_ext_fields :: ExtensibleFields

    Additional optional fields, where the Map key represents the field name, resulting in a (size, serialized data) pair. Because the data is intended to be serialized through the internal Binary class (increasing compatibility with types using Name and FastString, such as HIE), this format is chosen over ByteStrings.

Instances

Instances details
Binary ModIface Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

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

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () Source #

data SafeHaskellMode Source #

The various Safe Haskell modes

Constructors

Sf_None

inferred unsafe

Sf_Unsafe

declared and checked

Sf_Trustworthy

declared and checked

Sf_Safe

declared and checked

Sf_SafeInferred

inferred as safe

Sf_Ignore

-fno-safe-haskell state

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.

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

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.

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

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 DecoratedSDoc, 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 Source #

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.

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 GhcPs -> m ForeignHValue Source #

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

Docs

data GetDocsFailure Source #

Failure modes for getDocs.

Constructors

NameHasNoModule Name

nameModule_maybe returned Nothing.

NoDocsInIface

This is probably because the module was loaded without -haddock, but it's also possible that the entire module contains no documentation.

Fields

InteractiveName

The Name was defined interactively.

Instances

Instances details
Outputable GetDocsFailure Source # 
Instance details

Defined in GHC.Runtime.Eval

Other

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 ModBreaks Source #

All the information about the breakpoints for a module

Constructors

ModBreaks 

Fields

type BreakIndex = Int Source #

Breakpoint index

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

Abstract syntax elements

Units

Modules

type Module = GenModule Unit Source #

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

moduleName :: GenModule unit -> ModuleName Source #

Module name (e.g. A.B.C)

moduleUnit :: GenModule unit -> unit Source #

Unit the module belongs to

data ModuleName Source #

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

Instances

Instances details
Data ModuleName Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Show ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

NFData ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Methods

rnf :: ModuleName -> () Source #

Uniquable ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Binary ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Outputable ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc Source #

Eq ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Ord ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

type Anno ModuleName Source # 
Instance details

Defined in GHC.Hs.ImpExp

Names

data Name Source #

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

Instances

Instances details
Data Name Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c Name) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

NFData Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () Source #

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

Uniquable Name Source # 
Instance details

Defined in GHC.Types.Name

Binary Name Source #

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in GHC.Types.Name

Outputable Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc Source #

OutputableBndr Name Source # 
Instance details

Defined in GHC.Types.Name

Eq Name Source #

The same comments as for Name's Ord instance apply.

Instance details

Defined in GHC.Types.Name

Methods

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

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

Ord Name Source #

Caution: This instance is implemented via nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and trac #15240 for a bug caused by improper use of this instance.

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 #

type Anno Name Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

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

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

class NamedThing a where Source #

A class allowing convenient access to the Name of various datatypes

Minimal complete definition

getName

Methods

getOccName :: a -> OccName Source #

getName :: a -> Name Source #

Instances

Instances details
NamedThing Class Source # 
Instance details

Defined in GHC.Core.Class

NamedThing ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

NamedThing DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

NamedThing FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

NamedThing PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

NamedThing TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

NamedThing IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing Source # 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

NamedThing (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

NamedThing (Located a) => NamedThing (LocatedAn an a) Source # 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName Source #

getName :: VarBndr tv flag -> Name Source #

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

data RdrName Source #

Reader Name

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

Unqualified name

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

Qual ModuleName OccName

Qualified name

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

Instances details
Data RdrName Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

DisambInfixOp RdrName Source # 
Instance details

Defined in GHC.Parser.PostProcess

HasOccName RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc Source #

OutputableBndr RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Eq RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

Ord RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

type Anno RdrName Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

Identifiers

type Id = Var Source #

Identifier

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

isDeadEndId :: Var -> Bool Source #

Returns true if an application to n args diverges or throws an exception See Note [Dead ends] in GHC.Types.Demand.

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

Instances details
Data TyCon Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

NamedThing TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Uniquable TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc Source #

Eq TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

tyConTyVars :: TyCon -> [TyVar] Source #

TyVar binders

tyConDataCons :: TyCon -> [DataCon] Source #

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

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

Type variables

type TyVar = Var Source #

Type or kind Variable

Data constructors

data DataCon Source #

A data constructor

Instances

Instances details
Data DataCon Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

NamedThing DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Uniquable DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc Source #

OutputableBndr DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Eq DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

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

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

The type variables are quantified in the order that the user wrote them. See Note [DataCon user type variable binders].

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

data StrictnessMark Source #

Instances

Instances details
Outputable StrictnessMark Source # 
Instance details

Defined in GHC.Core.DataCon

Classes

data Class Source #

Instances

Instances details
Data Class Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c Class) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

NamedThing Class Source # 
Instance details

Defined in GHC.Core.Class

Uniquable Class Source # 
Instance details

Defined in GHC.Core.Class

Outputable Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc Source #

Eq Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

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

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

Instances

data ClsInst Source #

A type-class instance. Note that there is some tricky laziness at work here. See Note [ClsInst laziness and the rough-match fields] for more details.

Instances

Instances details
Data ClsInst Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

NamedThing ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Outputable ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc Source #

pprFamInst :: FamInst -> SDoc Source #

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

data FamInst Source #

Instances

Instances details
NamedThing FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc Source #

Types and Kinds

data Type Source #

Instances

Instances details
Data Type Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c Type) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc Source #

Eq (DeBruijn Type) Source # 
Instance details

Defined in GHC.Core.Map.Type

splitForAllTyCoVars :: Type -> ([TyCoVar], Type) Source #

Take a ForAllTy apart, returning the list of tycovars 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 constraint kind 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

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 GHC.Tc.Utils.Env for how to retrieve a TyThing given a Name.

Instances

Instances details
NamedThing TyThing Source # 
Instance details

Defined in GHC.Types.TyThing

Outputable TyThing Source # 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc Source #

Syntax

module GHC.Hs

Fixities

data FixityDirection Source #

Constructors

InfixL 
InfixR 
InfixN 

Instances

Instances details
Data FixityDirection Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Binary FixityDirection Source # 
Instance details

Defined in GHC.Types.Fixity

Outputable FixityDirection Source # 
Instance details

Defined in GHC.Types.Fixity

Eq FixityDirection Source # 
Instance details

Defined in GHC.Types.Fixity

data LexicalFixity Source #

Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.

Constructors

Prefix 
Infix 

Instances

Instances details
Data LexicalFixity Source # 
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 Source #

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

toConstr :: LexicalFixity -> Constr Source #

dataTypeOf :: LexicalFixity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable LexicalFixity Source # 
Instance details

Defined in GHC.Types.Fixity

Eq LexicalFixity Source # 
Instance details

Defined in GHC.Types.Fixity

Source locations

data SrcLoc Source #

Source Location

Instances

Instances details
Show SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc Source #

Eq SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

data RealSrcLoc Source #

Real Source Location

Represents a single point within a file

noSrcLoc :: SrcLoc Source #

Built-in "bad" SrcLoc values for particular locations

srcLocFile :: RealSrcLoc -> FastString Source #

Gives the filename of the SrcLoc

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 #

Source Span

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

Instances

Instances details
Data SrcSpan Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Show SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () Source #

Binary SrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

ToJson SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc Source #

Outputable SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc Source #

Eq SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

Binary a => Binary (Located a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

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

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

get :: BinHandle -> IO (Located a) Source #

Outputable e => Outputable (Located e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

data RealSrcSpan Source #

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

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

Real Source Span

Instances

Instances details
Data RealSrcSpan Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c RealSrcSpan) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Show RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Binary RealSrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

ToJson RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc Source #

Eq RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable e => Outputable (GenLocated RealSrcSpan e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

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

Instances details
Foldable (GenLocated l) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

foldMap :: Monoid m => (a -> m) -> GenLocated l a -> 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) Source # 
Instance details

Defined in GHC.Types.SrcLoc

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 #

Functor (GenLocated l) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

Binary a => Binary (LocatedL a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Binary a => Binary (Located a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

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

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

get :: BinHandle -> IO (Located a) Source #

Outputable e => Outputable (Located e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

(Data l, Data e) => Data (GenLocated l e) Source # 
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) 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 t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) Source #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> 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 :: forall r r'. (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 #

Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source #

toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source #

dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source #

Data (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source #

toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source #

dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source #

Data (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source #

toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source #

dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source #

Data (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source #

toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source #

dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source #

Data (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source #

toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source #

Data (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source #

toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source #

Data (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source #

toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source #

Data (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source #

toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source #

Data (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) Source #

toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source #

dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source #

Data (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) Source #

toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source #

dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source #

Data (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) Source #

toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source #

dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source #

Data (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) Source #

toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source #

dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source #

Data (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source #

toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source #

Data (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source #

toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source #

Data (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source #

toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source #

Data (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source #

toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source #

NamedThing (Located a) => NamedThing (LocatedAn an a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc Source #

Outputable e => Outputable (GenLocated RealSrcSpan e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

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

Defined in GHC.Types.SrcLoc

Methods

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

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

(Ord l, Ord e) => Ord (GenLocated l e) Source # 
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 #

Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source #

Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source #

Data (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source #

Data (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source #

Data (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source #

Data (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source #

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Expr

Constructing Located

noLoc :: e -> Located e Source #

Deconstructing Located

unLoc :: GenLocated l e -> e Source #

Combining and comparing Located values

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

Tests whether the two located things are equal

cmpLocated :: Ord a => GenLocated l a -> GenLocated l 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 #

Strategies for ordering SrcSpans

leftmost_largest :: SrcSpan -> SrcSpan -> Ordering Source #

Strategies for ordering SrcSpans

rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering Source #

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 :: SDocContext -> GhcException -> ShowS Source #

Append a description of the given exception to this string.

newtype GhcApiError Source #

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

Constructors

GhcApiError String 

Token stream manipulations

data Token Source #

Instances

Instances details
Show Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Outputable Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc Source #

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

Exact print 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 otherwise captured in the AST.

The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/in-tree-api-annotations

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

Constructors

AnnAnyclass 
AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseB

'|)'

AnnCloseBU

'|)', unicode variant

AnnCloseC

'}'

AnnCloseQ

'|]'

AnnCloseQU

'|]', unicode variant

AnnCloseP

')'

AnnClosePH

'#)'

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 
AnnLollyU

The unicode arrow

AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnName

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

AnnOf 
AnnOpen

'{-# DEPRECATED' etc. Opening of pragmas where the capitalisation of the string can be changed by the user. The actual text used is stored in a SourceText on the relevant pragma item.

AnnOpenB

'(|'

AnnOpenBU

'(|', unicode variant

AnnOpenC

'{'

AnnOpenE

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

AnnOpenEQ

'[|'

AnnOpenEQU

'[|', unicode variant

AnnOpenP

'('

AnnOpenS

'['

AnnOpenPH

'(#'

AnnDollar

prefix $ -- TemplateHaskell

AnnDollarDollar

prefix $$ -- TemplateHaskell

AnnPackageName 
AnnPattern 
AnnPercent

% -- for HsExplicitMult

AnnPercentOne

'%1' -- for HsLinearArrow

AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThTyQuote

double '''

AnnTilde

~

AnnType 
AnnUnit

() for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnVia

via

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

->

AnnrarrowtailU

->, unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

Instances

Instances details
Data AnnKeywordId Source # 
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 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 t => (forall d. Data d => c (t d)) -> Maybe (c AnnKeywordId) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Show AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Eq AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Ord AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

data EpaComment Source #

Constructors

EpaComment 

Fields

Instances

Instances details
Data EpaComment Source # 
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) -> EpaComment -> c EpaComment Source #

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

toConstr :: EpaComment -> Constr Source #

dataTypeOf :: EpaComment -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc Source #

Eq EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Ord EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

Miscellaneous