ghcide-2.0.0.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageHaskell2010

Development.IDE.GHC.Compat.Core

Description

Compat Core module that handles the GHC module hierarchy re-organisation by re-exporting everything we care about.

This module provides no other compat mechanisms, except for simple backward-compatible pattern synonyms.

Synopsis

Session

data DynFlags #

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

packageFlags :: DynFlags -> [PackageFlag] #

The -package and -hide-package flags from the command-line. In *reverse* order that they're specified on the command line.

flagsForCompletion :: Bool -> [String] #

Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.

refLevelHoleFits :: DynFlags -> Maybe Int #

Maximum level of refinement for refinement hole fits in typed hole error messages

maxRefHoleFits :: DynFlags -> Maybe Int #

Maximum number of refinement hole fits to show in typed hole error messages

maxValidHoleFits :: DynFlags -> Maybe Int #

Maximum number of hole fits to show in typed hole error messages

lookupType :: HscEnv -> Name -> IO (Maybe TyThing) #

Find the TyThing for the given Name by using all the resources at our disposal: the compiled modules in the HomePackageTable and the compiled modules in other packages that live in PackageTypeEnv. Note that this does NOT look up the TyThing in the module being compiled: you have to do that yourself, if desired

loadWiredInHomeIface :: Name -> IfM lcl () #

An IfM function to load the home interface for a wired-in thing, so that we're sure that we see its instance declarations and rules See Note [Loading instances for wired-in things]

loadSysInterface :: SDoc -> Module -> IfM lcl ModIface #

Loads a system interface and throws an exception if it fails

type CommandLineOption = String #

Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type

settings :: DynFlags -> Settings #

"unbuild" a Settings from a DynFlags. This shouldn't be needed in the vast majority of code. But GHCi questionably uses this to produce a default DynFlags from which to compute a flags diff for printing.

gopt :: GeneralFlag -> DynFlags -> Bool #

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.

wopt :: WarningFlag -> DynFlags -> Bool #

Test whether a WarningFlag is set

xFlags :: [FlagSpec Extension] #

These -Xblah flags can all be reversed with -XNoblah

xopt :: Extension -> DynFlags -> Bool #

Test whether a Extension is set

data FlagSpec flag #

Constructors

FlagSpec 

Fields

data WarningFlag #

Constructors

Opt_WarnDuplicateExports 
Opt_WarnDuplicateConstraints 
Opt_WarnRedundantConstraints 
Opt_WarnHiShadows 
Opt_WarnImplicitPrelude 
Opt_WarnIncompletePatterns 
Opt_WarnIncompleteUniPatterns 
Opt_WarnIncompletePatternsRecUpd 
Opt_WarnOverflowedLiterals 
Opt_WarnEmptyEnumerations 
Opt_WarnMissingFields 
Opt_WarnMissingImportList 
Opt_WarnMissingMethods 
Opt_WarnMissingSignatures 
Opt_WarnMissingLocalSignatures 
Opt_WarnNameShadowing 
Opt_WarnOverlappingPatterns 
Opt_WarnTypeDefaults 
Opt_WarnMonomorphism 
Opt_WarnUnusedTopBinds 
Opt_WarnUnusedLocalBinds 
Opt_WarnUnusedPatternBinds 
Opt_WarnUnusedImports 
Opt_WarnUnusedMatches 
Opt_WarnUnusedTypePatterns 
Opt_WarnUnusedForalls 
Opt_WarnUnusedRecordWildcards 
Opt_WarnRedundantBangPatterns 
Opt_WarnRedundantRecordWildcards 
Opt_WarnWarningsDeprecations 
Opt_WarnDeprecatedFlags 
Opt_WarnMissingMonadFailInstances 
Opt_WarnSemigroup 
Opt_WarnDodgyExports 
Opt_WarnDodgyImports 
Opt_WarnOrphans 
Opt_WarnAutoOrphans 
Opt_WarnIdentities 
Opt_WarnTabs 
Opt_WarnUnrecognisedPragmas 
Opt_WarnDodgyForeignImports 
Opt_WarnUnusedDoBind 
Opt_WarnWrongDoBind 
Opt_WarnAlternativeLayoutRuleTransitional 
Opt_WarnUnsafe 
Opt_WarnSafe 
Opt_WarnTrustworthySafe 
Opt_WarnMissedSpecs 
Opt_WarnAllMissedSpecs 
Opt_WarnUnsupportedCallingConventions 
Opt_WarnUnsupportedLlvmVersion 
Opt_WarnMissedExtraSharedLib 
Opt_WarnInlineRuleShadowing 
Opt_WarnTypedHoles 
Opt_WarnPartialTypeSignatures 
Opt_WarnMissingExportedSignatures 
Opt_WarnUntickedPromotedConstructors 
Opt_WarnDerivingTypeable 
Opt_WarnDeferredTypeErrors 
Opt_WarnDeferredOutOfScopeVariables 
Opt_WarnNonCanonicalMonadInstances 
Opt_WarnNonCanonicalMonadFailInstances 
Opt_WarnNonCanonicalMonoidInstances 
Opt_WarnMissingPatternSynonymSignatures 
Opt_WarnUnrecognisedWarningFlags 
Opt_WarnSimplifiableClassConstraints 
Opt_WarnCPPUndef 
Opt_WarnUnbangedStrictPatterns 
Opt_WarnMissingHomeModules 
Opt_WarnPartialFields 
Opt_WarnMissingExportList 
Opt_WarnInaccessibleCode 
Opt_WarnStarIsType 
Opt_WarnStarBinder 
Opt_WarnImplicitKindVars 
Opt_WarnSpaceAfterBang 
Opt_WarnMissingDerivingStrategies 
Opt_WarnPrepositiveQualifiedModule 
Opt_WarnUnusedPackages 
Opt_WarnInferredSafeImports 
Opt_WarnMissingSafeHaskellMode 
Opt_WarnCompatUnqualifiedImports 
Opt_WarnDerivingDefaults 
Opt_WarnInvalidHaddock 
Opt_WarnOperatorWhitespaceExtConflict 
Opt_WarnOperatorWhitespace 
Opt_WarnAmbiguousFields 
Opt_WarnImplicitLift 
Opt_WarnMissingKindSignatures 
Opt_WarnUnicodeBidirectionalFormatCharacters 

data GeneralFlag #

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

Flags for manipulating packages visibility.

Instances

Instances details
Show PackageFlag Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Outputable PackageFlag 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageFlag -> SDoc #

Eq PackageFlag 
Instance details

Defined in GHC.Driver.Session

data PackageArg #

We accept flags which make packages visible, but how they select the package varies; this data type reflects what selection criterion is used.

Constructors

PackageArg String

-package, by PackageName

UnitIdArg Unit

-package-id, by Unit

Instances

Instances details
Show PackageArg 
Instance details

Defined in GHC.Driver.Session

Outputable PackageArg 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageArg -> SDoc #

Eq PackageArg 
Instance details

Defined in GHC.Driver.Session

data ModRenaming #

Represents the renaming that may be associated with an exposed package, e.g. the rns part of -package "foo (rns)".

Here are some example parsings of the package flags (where a string literal is punned to be a ModuleName:

  • -package foo is ModRenaming True []
  • -package foo () is ModRenaming False []
  • -package foo (A) is ModRenaming False [(A, A)]
  • -package foo (A as B) is ModRenaming False [(A, B)]
  • -package foo with (A as B) is ModRenaming True [(A, B)]

Constructors

ModRenaming 

Fields

Instances

Instances details
Outputable ModRenaming 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: ModRenaming -> SDoc #

Eq ModRenaming 
Instance details

Defined in GHC.Driver.Session

parseDynamicFlagsCmdLine #

Arguments

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

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

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

parseDynamicFilePragma #

Arguments

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

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

Like parseDynamicFlagsCmdLine but does not allow the package flags (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). Used to parse flags set in a modules pragma.

data WarnReason #

Used when outputting warnings: if a reason is given, it is displayed. If a warning isn't controlled by a flag, this is made explicit at the point of use.

Constructors

NoReason 
Reason !WarningFlag

Warning was enabled with the flag

ErrReason !(Maybe WarningFlag)

Warning was made an error because of -Werror or -Werror=WarningFlag

Instances

Instances details
Show WarnReason 
Instance details

Defined in GHC.Driver.Flags

ToJson WarnReason 
Instance details

Defined in GHC.Driver.Flags

Methods

json :: WarnReason -> JsonDoc #

Outputable WarnReason 
Instance details

Defined in GHC.Driver.Flags

Methods

ppr :: WarnReason -> SDoc #

wWarningFlags :: [FlagSpec WarningFlag] #

These -W<blah> flags can all be reversed with -Wno-<blah>

updOptLevel :: Int -> DynFlags -> DynFlags #

Sets the DynFlags to be appropriate to the optimisation level

Linear Haskell

scaledThing :: Scaled a -> a #

Interface Files

type IfaceExport = AvailInfo #

The original names declared of a certain module that are exported

data IfaceTyCon #

Instances

Instances details
NFData IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

rnf :: IfaceTyCon -> () #

Binary IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyCon -> SDoc #

Eq IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

type ModIface = ModIface_ 'ModIfaceFinal #

data ModIface_ (phase :: ModIfacePhase) #

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

Defined in GHC.Unit.Module.ModIface

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

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () #

data HscSource #

Constructors

HsSrcFile

.hs file

HsBootFile

.hs-boot file

HsigFile

.hsig file

Instances

Instances details
Show HscSource 
Instance details

Defined in GHC.Types.SourceFile

Binary HscSource 
Instance details

Defined in GHC.Types.SourceFile

Eq HscSource 
Instance details

Defined in GHC.Types.SourceFile

Ord HscSource 
Instance details

Defined in GHC.Types.SourceFile

data WhereFrom #

Instances

Instances details
Outputable WhereFrom 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc #

data SourceModified #

Indicates whether a given module's source has been modified since it was last compiled.

Constructors

SourceModified

the source has been modified

SourceUnmodified

the source has not been modified. Compilation may or may not be necessary, depending on whether any dependencies have changed since we last compiled.

SourceUnmodifiedAndStable

the source has not been modified, and furthermore all of its (transitive) dependencies are up to date; it definitely does not need to be recompiled. This is important for two reasons: (a) we can omit the version check in checkOldIface, and (b) if the module used TH splices we don't need to force recompilation.

loadModuleInterface :: SDoc -> Module -> TcM ModIface #

Load interface directly for a fully qualified Module. (This is a fairly rare operation, but in particular it is used to load orphan modules in order to pull their instances into the global package table and to handle some operations in GHCi).

data RecompileRequired #

Constructors

UpToDate

everything is up to date, recompilation is not required

MustCompile

The .hs file has been touched, or the .o/.hi file does not exist

RecompBecause String

The .o/.hi files are up to date, but something else has changed to force recompilation; the String says what (one-line summary)

mkFullIface :: HscEnv -> PartialModIface -> Maybe CgInfos -> IO ModIface #

Fully instantiate an interface. Adds fingerprints and potentially code generator produced information.

CgInfos is not available when not generating code (-fno-code), or when not generating interface pragmas (-fomit-interface-pragmas). See also Note [Conveying CAF-info and LFInfo between modules] in GHC.StgToCmm.Types.

checkOldIface :: HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> IO (RecompileRequired, Maybe ModIface) #

Top level function to check if the version of an old interface file is equivalent to the current source file the user asked us to compile. If the same, we can avoid recompilation. We return a tuple where the first element is a bool saying if we should recompile the object file and the second is maybe the interface file, where Nothing means to rebuild the interface file and not use the existing one.

data IsBootInterface #

Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

toConstr :: IsBootInterface -> Constr #

dataTypeOf :: IsBootInterface -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Binary IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Eq IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Ord IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Fixity

data LexicalFixity #

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

Defined in GHC.Types.Fixity

Methods

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

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

toConstr :: LexicalFixity -> Constr #

dataTypeOf :: LexicalFixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: LexicalFixity -> SDoc #

Eq LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

data Fixity #

Instances

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

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

toConstr :: Fixity -> Constr #

dataTypeOf :: Fixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

put_ :: BinHandle -> Fixity -> IO () #

put :: BinHandle -> Fixity -> IO (Bin Fixity) #

get :: BinHandle -> IO Fixity #

Outputable Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: Fixity -> SDoc #

Eq Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

mi_fix :: ModIface -> OccName -> Fixity #

Lookups up a (possibly cached) fixity from a ModIface_. If one cannot be found, defaultFixity is returned instead.

ModSummary

data ModSummary #

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
Show ModSummary Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModSummary Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModSummary -> () #

Outputable ModSummary 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc #

HomeModInfo

data HomeModInfo #

Information about modules in the package being compiled

Constructors

HomeModInfo 

Fields

Instances

Instances details
Show HomeModInfo Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData HomeModInfo Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: HomeModInfo -> () #

ModGuts

data ModGuts #

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

Constructors

ModGuts 

Fields

Instances

Instances details
Show ModGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModGuts -> () #

data CgGuts #

A restricted form of ModGuts for code generation purposes

Constructors

CgGuts 

Fields

Instances

Instances details
Show CgGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData CgGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: CgGuts -> () #

ModDetails

data ModDetails #

The ModDetails is essentially a cache for information in the ModIface for home modules only. Information relating to packages will be loaded into global environments in ExternalPackageState.

Constructors

ModDetails 

Fields

Instances

Instances details
Show ModDetails Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModDetails Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModDetails -> () #

HsExpr,

Var

data Type #

Constructors

TyVarTy Var

Vanilla type or kind variable (*never* a coercion variable)

AppTy Type Type

Type application to something other than a TyCon. Parameters:

1) Function: must not be a TyConApp or CastTy, must be another AppTy, or TyVarTy See Note [Respecting definitional equality] (EQ1) about the no CastTy requirement

2) Argument type

TyConApp TyCon [KindOrType]

Application of a TyCon, including newtypes and synonyms. Invariant: saturated applications of FunTyCon must use FunTy and saturated synonyms must use their own constructors. However, unsaturated FunTyCons do appear as TyConApps. Parameters:

1) Type constructor being applied to.

2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym.

ForAllTy !TyCoVarBinder Type

A Π type. INVARIANT: If the binder is a coercion variable, it must be mentioned in the Type. See Note [Unused coercion variable in ForAllTy]

LitTy TyLit

Type literals are similar to type constructors.

CastTy Type KindCoercion

A kind cast. The coercion is always nominal. INVARIANT: The cast is never reflexive (EQ2) INVARIANT: The Type is not a CastTy (use TransCo instead) (EQ3) INVARIANT: The Type is not a ForAllTy over a tyvar (EQ4) See Note [Respecting definitional equality]

CoercionTy Coercion

Injection of a Coercion into a type This should only ever be used in the RHS of an AppTy, in the list of a TyConApp, when applying a promoted GADT data constructor

Instances

Instances details
Data Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData Type Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc #

Eq (DeBruijn Type) 
Instance details

Defined in GHC.Core.Map.Type

pattern FunTy :: Type -> Type -> Type Source #

mkVisFunTys :: [Scaled Type] -> Type -> Type #

Make nested arrow types

Specs

data ImpDeclSpec #

Import Declaration Specification

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

  • is_mod :: ModuleName

    Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

  • is_as :: ModuleName

    Import alias, e.g. from as M (or Muggle if there is no as clause)

  • is_qual :: Bool

    Was this import qualified?

  • is_dloc :: SrcSpan

    The location of the entire import declaration

Instances

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

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

toConstr :: ImpDeclSpec -> Constr #

dataTypeOf :: ImpDeclSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ImpDeclSpec 
Instance details

Defined in GHC.Types.Name.Reader

data ImportSpec #

Import Specification

The ImportSpec of something says how it came to be imported It's quite elaborate so that we can give accurate unused-name warnings.

Constructors

ImpSpec 

Instances

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

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

toConstr :: ImportSpec -> Constr #

dataTypeOf :: ImportSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc #

Eq ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

SourceText

data SourceText #

Constructors

SourceText String 
NoSourceText

For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item.

Instances

Instances details
Data SourceText 
Instance details

Defined in GHC.Types.SourceText

Methods

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

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

toConstr :: SourceText -> Constr #

dataTypeOf :: SourceText -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SourceText 
Instance details

Defined in GHC.Types.SourceText

Binary SourceText 
Instance details

Defined in GHC.Types.SourceText

Outputable SourceText 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc #

Eq SourceText 
Instance details

Defined in GHC.Types.SourceText

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

Name

tyThingParent_maybe :: TyThing -> Maybe TyThing #

tyThingParent_maybe x returns (Just p) when pprTyThingInContext should print a declaration for p (albeit with some "..." in it) when asked to show x It returns the *immediate* parent. So a datacon returns its tycon but the tycon could be the associated type of a class, so it in turn might have a parent.

Ways

data Way #

A way

Don't change the constructor order as it us used by waysTag to create a unique tag (e.g. thr_debug_p) which is expected by other tools (e.g. Cabal).

Instances

Instances details
Show Way 
Instance details

Defined in GHC.Platform.Ways

Methods

showsPrec :: Int -> Way -> ShowS #

show :: Way -> String #

showList :: [Way] -> ShowS #

Eq Way 
Instance details

Defined in GHC.Platform.Ways

Methods

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

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

Ord Way 
Instance details

Defined in GHC.Platform.Ways

Methods

compare :: Way -> Way -> Ordering #

(<) :: Way -> Way -> Bool #

(<=) :: Way -> Way -> Bool #

(>) :: Way -> Way -> Bool #

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

max :: Way -> Way -> Way #

min :: Way -> Way -> Way #

wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #

Turn these flags on when enabling this way

wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #

Turn these flags off when enabling this way

AvailInfo

data AvailInfo #

Records what things are "available", i.e. in scope

Instances

Instances details
Data AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

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

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

toConstr :: AvailInfo -> Constr #

dataTypeOf :: AvailInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary AvailInfo 
Instance details

Defined in GHC.Types.Avail

Outputable AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc #

Eq AvailInfo

Used when deciding if the interface has changed

Instance details

Defined in GHC.Types.Avail

pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo Source #

availName :: AvailInfo -> Name #

Just the main name made available, i.e. not the available pieces of type or class brought into scope by the AvailInfo

availNames :: AvailInfo -> [Name] #

All names made available by the availability information (excluding overloaded selectors)

availNamesWithSelectors :: AvailInfo -> [Name] #

All names made available by the availability information (including overloaded selectors)

TcGblEnv

data TcGblEnv #

TcGblEnv describes the top-level of the module at the point at which the typechecker is finished work. It is this structure that is handed on to the desugarer For state that needs to be updated during the typechecking phase and returned at end, use a TcRef (= IORef).

Constructors

TcGblEnv 

Fields

Instances

Instances details
ContainsModule TcGblEnv 
Instance details

Defined in GHC.Tc.Types

Parsing and LExer types

data HsModule #

Haskell Module

All we actually declare here is the top-level structure for a module.

Constructors

HsModule 

Fields

Instances

Instances details
Data HsModule 
Instance details

Defined in GHC.Hs

Methods

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

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

toConstr :: HsModule -> Constr #

dataTypeOf :: HsModule -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData HsModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: HsModule -> () #

Outputable HsModule 
Instance details

Defined in GHC.Hs

Methods

ppr :: HsModule -> SDoc #

Compilation Main

data HscEnv #

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 #

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.

unGhc :: Ghc a -> Session -> IO a #

data Session #

The Session is a handle to the complete state of a compilation session. A compilation session consists of a set of modules constituting the current program or library, the context for interactive evaluation, and various caches.

Constructors

Session !(IORef HscEnv) 

modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () #

Set the current session to the result of applying the current session to the argument.

setSessionDynFlags :: GhcMonad m => DynFlags -> m () #

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

getSessionDynFlags :: GhcMonad m => m DynFlags #

Grabs the DynFlags from the Session

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

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

In short, a GHC monad

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

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

Minimal complete definition

getSession, setSession

Instances

Instances details
GhcMonad Ghc 
Instance details

Defined in GHC.Driver.Monad

ExceptionMonad m => GhcMonad (GhcT m) 
Instance details

Defined in GHC.Driver.Monad

Methods

getSession :: GhcT m HscEnv #

setSession :: HscEnv -> GhcT m () #

data Ghc a #

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

Defined in GHC.Driver.Monad

Methods

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

MonadIO Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> Ghc a #

Applicative Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> Ghc a #

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

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

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

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

Functor Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Monad Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

return :: a -> Ghc a #

MonadCatch Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

MonadMask Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

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

MonadThrow Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

GhcMonad Ghc 
Instance details

Defined in GHC.Driver.Monad

HasDynFlags Ghc 
Instance details

Defined in GHC.Driver.Monad

HasLogger Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

getLogger :: Ghc Logger #

runHsc :: HscEnv -> Hsc a -> IO a #

data Phase #

Instances

Instances details
Show Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

Outputable Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc #

Eq Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

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

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

hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts #

Convert a typechecked module to Core

hscGenHardCode #

Arguments

:: HscEnv 
-> CgGuts 
-> ModLocation 
-> FilePath 
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)], CgInfos)

Just f = _stub.c is f

Compile to hard-code.

hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts #

Run Core2Core simplifier. The list of String is a list of (Core) plugin module names added via TH (cf addCorePlugin).

hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) #

Rename and typecheck a module, additionally returning the renamed syntax

Typecheck utils

initTidyOpts :: HscEnv -> IO TidyOpts Source #

data ImportedModsVal #

Constructors

ImportedModsVal 

Fields

Source Locations

class HasSrcSpan a Source #

Minimal complete definition

getLoc

Instances

Instances details
HasSrcSpan SrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

HasSrcSpan (SrcSpanAnn' ann) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

Methods

getLoc :: SrcSpanAnn' ann -> SrcSpan Source #

HasSrcSpan (GenLocated (SrcSpanAnn' ann) a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

HasSrcSpan (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

unLoc :: GenLocated l e -> e #

noLocA :: a -> LocatedAn an a Source #

unLocA :: forall pass a. XRec (GhcPass pass) a -> a Source #

data AnnListItem #

Annotation for items appearing in a list. They can have one or more trailing punctuations items, such as commas or semicolons.

Constructors

AnnListItem 

Instances

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

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

toConstr :: AnnListItem -> Constr #

dataTypeOf :: AnnListItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid AnnListItem 
Instance details

Defined in GHC.Parser.Annotation

Semigroup AnnListItem 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnListItem 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnListItem -> SDoc #

Eq AnnListItem 
Instance details

Defined in GHC.Parser.Annotation

HasLoc (LocatedA a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedA a -> SrcSpan

HiePass p => HasType (LocatedA (HsBind (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsBind (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (HsExpr (GhcPass p)))

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (Pat (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (Pat (GhcPass p)) -> HieM [HieAST Type]

ToHie (LocatedA (ImportDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ImportDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA HsWrapper) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA HsWrapper -> HieM [HieAST Type]

ToHie (LocatedA (FixitySig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FixitySig GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FunDep GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FunDep GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsCmd (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsSplice (GhcPass p)) -> HieM [HieAST Type]

(HiePass p, Data (body (GhcPass p)), AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

ToHie (LocatedA (ConDeclField GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDeclField GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (HsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsType GhcRn) -> HieM [HieAST Type]

ToHie (LocatedC [LocatedA (HsType GhcRn)]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedC [LocatedA (HsType GhcRn)] -> HieM [HieAST Type]

ToHie (LocatedL [LocatedA (ConDeclField GhcRn)]) 
Instance details

Defined in Compat.HieAst

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LocatedA (HsBind (GhcPass p))) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedA a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedA a) -> HieM [HieAST Type]

ToHie (EvBindContext (LocatedA TcEvBinds)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: EvBindContext (LocatedA TcEvBinds) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA (IE GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA (IE GhcRn)) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA ModuleName) -> HieM [HieAST Type]

HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (LocatedA (Pat (GhcPass p))) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data arg, Data label) => ToHie (RContext (LocatedA (HsRecField' label arg))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LocatedA (HsRecField' label arg)) -> HieM [HieAST Type]

HiePass p => ToHie (RScoped (LocatedA (IPBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (IPBind (GhcPass p))) -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), AnnoBody p body, HiePass p) => ToHie (RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p)))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p))))) -> HieM [HieAST Type]

HiePass p => ToHie (SigContext (LocatedA (Sig (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LocatedA (Sig (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LocatedA (HsSigType GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LocatedA (HsSigType GhcRn)) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

Data flag => ToHie (TVScoped (LocatedA (HsTyVarBndr flag GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LocatedA (HsTyVarBndr flag GhcRn)) -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

(HiePass p, AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

data NameAnn #

exact print annotations for a RdrName. There are many kinds of adornment that can be attached to a given RdrName. This type captures them, as detailed on the individual constructors.

Constructors

NameAnn

Used for a name with an adornment, so `foo`, (bar)

NameAnnCommas

Used for (,,,), or @()#

NameAnnOnly

Used for (), (##), []

NameAnnRArrow

Used for ->, as an identifier

NameAnnQuote

Used for an item with a leading '. The annotation for unquoted item is stored in nann_quoted.

NameAnnTrailing

Used when adding a TrailingAnn to an existing LocatedN which has no Api Annotation (via the EpAnnNotUsed constructor.

Instances

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

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

toConstr :: NameAnn -> Constr #

dataTypeOf :: NameAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid NameAnn 
Instance details

Defined in GHC.Parser.Annotation

Semigroup NameAnn 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAnn -> SDoc #

Eq NameAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

HasLoc (LocatedN a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedN a -> SrcSpan

ToHie (LBooleanFormula (LocatedN Name)) 
Instance details

Defined in Compat.HieAst

ToHie (Context (Located a)) => ToHie (Context (LocatedN a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedN a) -> HieM [HieAST Type]

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

data GenLocated l e #

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

Constructors

L l e 

Instances

Instances details
Bifunctor GenLocated Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

bimap :: (a -> b) -> (c -> d) -> GenLocated a c -> GenLocated b d #

first :: (a -> b) -> GenLocated a c -> GenLocated b c #

second :: (b -> c) -> GenLocated a b -> GenLocated a c #

Foldable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

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

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

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

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

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

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

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

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

null :: GenLocated l a -> Bool #

length :: GenLocated l a -> Int #

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

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

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

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

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

Traversable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

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

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

Functor (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

Binary a => Binary (LocatedL a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

put_ :: BinHandle -> LocatedL a -> IO () #

put :: BinHandle -> LocatedL a -> IO (Bin (LocatedL a)) #

get :: BinHandle -> IO (LocatedL a) #

Binary a => Binary (Located a) 
Instance details

Defined in GHC.Utils.Binary

Methods

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

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

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

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

HasLoc (LocatedA a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedA a -> SrcSpan

HasLoc (LocatedN a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedN a -> SrcSpan

HasLoc (Located a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: Located a -> SrcSpan

HiePass p => HasType (LocatedA (HsBind (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsBind (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (HsExpr (GhcPass p)))

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (Pat (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (Pat (GhcPass p)) -> HieM [HieAST Type]

ToHie (LBooleanFormula (LocatedN Name)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (ImportDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ImportDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA HsWrapper) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA HsWrapper -> HieM [HieAST Type]

ToHie (LocatedA (FixitySig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FixitySig GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FunDep GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FunDep GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsCmd (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsSplice (GhcPass p)) -> HieM [HieAST Type]

(HiePass p, Data (body (GhcPass p)), AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

ToHie (LocatedA (ConDeclField GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDeclField GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (HsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsType GhcRn) -> HieM [HieAST Type]

ToHie (LocatedC (DerivClauseTys GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedC [LocatedA (HsType GhcRn)]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedC [LocatedA (HsType GhcRn)] -> HieM [HieAST Type]

ToHie (LocatedL [LocatedA (ConDeclField GhcRn)]) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedP OverlapMode) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedP OverlapMode -> HieM [HieAST Type]

HiePass p => ToHie (Located (PatSynBind (GhcPass p) (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (PatSynBind (GhcPass p) (GhcPass p)) -> HieM [HieAST Type]

ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

ToHie (Located (HsDerivingClause GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (Located (InjectivityAnn GhcRn)) 
Instance details

Defined in Compat.HieAst

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

HiePass p => ToHie (Located (HsCmdTop (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (HsCmdTop (GhcPass p)) -> HieM [HieAST Type]

ToHie (Located HsIPName) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located HsIPName -> HieM [HieAST Type]

ToHie (Located [Located (HsDerivingClause GhcRn)]) 
Instance details

Defined in Compat.HieAst

HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LocatedA (HsBind (GhcPass p))) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedA a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedA a) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedN a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedN a) -> HieM [HieAST Type]

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> HieM [HieAST Type]

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

ToHie (Context (Located NoExtField)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located NoExtField) -> HieM [HieAST Type]

ToHie (EvBindContext (LocatedA TcEvBinds)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: EvBindContext (LocatedA TcEvBinds) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA (IE GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA (IE GhcRn)) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA ModuleName) -> HieM [HieAST Type]

ToHie (IEContext (Located FieldLabel)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located FieldLabel) -> HieM [HieAST Type]

HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (LocatedA (Pat (GhcPass p))) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data arg, Data label) => ToHie (RContext (LocatedA (HsRecField' label arg))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LocatedA (HsRecField' label arg)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcTc)) -> HieM [HieAST Type]

HiePass p => ToHie (RScoped (LocatedA (IPBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (IPBind (GhcPass p))) -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), AnnoBody p body, HiePass p) => ToHie (RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p)))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p))))) -> HieM [HieAST Type]

ToHie (RScoped (Located (FamilyResultSig GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (FamilyResultSig GhcRn)) -> HieM [HieAST Type]

ToHie (RScoped (Located (RuleBndr GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (RuleBndr GhcRn)) -> HieM [HieAST Type]

HiePass p => ToHie (SigContext (LocatedA (Sig (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LocatedA (Sig (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LocatedA (HsSigType GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LocatedA (HsSigType GhcRn)) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

Data flag => ToHie (TVScoped (LocatedA (HsTyVarBndr flag GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LocatedA (HsTyVarBndr flag GhcRn)) -> HieM [HieAST Type]

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

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: GenLocated l e -> Constr #

dataTypeOf :: GenLocated l e -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Show (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

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

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: GenLocated l e -> () #

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

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

Outputable (GenLocated Anchor EpaComment) 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Parser.Annotation

Methods

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

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

Defined in GHC.Types.SrcLoc

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) 
Instance details

Defined in Language.Haskell.Syntax.Type

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

Defined in GHC.Types.SrcLoc

Methods

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

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

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

Defined in GHC.Types.SrcLoc

Methods

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

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

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

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

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

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

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

HasSrcSpan (GenLocated (SrcSpanAnn' ann) a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

HasSrcSpan (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

(HiePass p, AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Type

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

data SrcSpan #

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

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: SrcSpan -> Constr #

dataTypeOf :: SrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () #

Binary SrcSpan 
Instance details

Defined in GHC.Utils.Binary

ToJson SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

Eq SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord SrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

HasSrcSpan SrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

Binary a => Binary (Located a) 
Instance details

Defined in GHC.Utils.Binary

Methods

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

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

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

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

HasLoc (Located a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: Located a -> SrcSpan

HiePass p => ToHie (Located (PatSynBind (GhcPass p) (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (PatSynBind (GhcPass p) (GhcPass p)) -> HieM [HieAST Type]

ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

ToHie (Located (HsDerivingClause GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (Located (InjectivityAnn GhcRn)) 
Instance details

Defined in Compat.HieAst

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

HiePass p => ToHie (Located (HsCmdTop (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (HsCmdTop (GhcPass p)) -> HieM [HieAST Type]

ToHie (Located HsIPName) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located HsIPName -> HieM [HieAST Type]

ToHie (Located [Located (HsDerivingClause GhcRn)]) 
Instance details

Defined in Compat.HieAst

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> HieM [HieAST Type]

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

ToHie (Context (Located NoExtField)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located NoExtField) -> HieM [HieAST Type]

ToHie (IEContext (Located FieldLabel)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located FieldLabel) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcTc)) -> HieM [HieAST Type]

ToHie (RScoped (Located (FamilyResultSig GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (FamilyResultSig GhcRn)) -> HieM [HieAST Type]

ToHie (RScoped (Located (RuleBndr GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (RuleBndr GhcRn)) -> HieM [HieAST Type]

Outputable a => Show (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) 
Instance details

Defined in Language.Haskell.Syntax.Type

HasSrcSpan (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

data RealSrcSpan #

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
FromJSON RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

ToJSON RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Data RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: RealSrcSpan -> Constr #

dataTypeOf :: RealSrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

NFData RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: RealSrcSpan -> () #

Binary RealSrcSpan 
Instance details

Defined in GHC.Utils.Binary

ToJson RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc #

Outputable RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc #

Eq RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

MapAge RealSrcSpan Source # 
Instance details

Defined in Development.IDE.Core.UseStale

Methods

mapAgeFrom :: forall (from :: Age) (to :: Age). PositionMap from to -> Tracked to RealSrcSpan -> Maybe (Tracked from RealSrcSpan) Source #

mapAgeTo :: forall (from :: Age) (to :: Age). PositionMap from to -> Tracked from RealSrcSpan -> Maybe (Tracked to RealSrcSpan) Source #

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

Defined in GHC.Types.SrcLoc

data RealSrcLoc #

Real Source Location

Represents a single point within a file

Instances

Instances details
Show RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc #

Eq RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

data SrcLoc #

Source Location

Constructors

UnhelpfulLoc FastString 

Instances

Instances details
Show SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc #

Eq SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

data BufSpan #

StringBuffer Source Span

Instances

Instances details
Semigroup BufSpan 
Instance details

Defined in GHC.Types.SrcLoc

Show BufSpan 
Instance details

Defined in GHC.Types.SrcLoc

Binary BufSpan 
Instance details

Defined in GHC.Utils.Binary

Eq BufSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord BufSpan 
Instance details

Defined in GHC.Types.SrcLoc

data SrcSpanAnn' a #

The 'SrcSpanAnn'' type wraps a normal SrcSpan, together with an extra annotation type. This is mapped to a specific GenLocated usage in the AST through the XRec and Anno type families.

Instances

Instances details
Functor SrcSpanAnn' Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

fmap :: (a -> b) -> SrcSpanAnn' a -> SrcSpanAnn' b #

(<$) :: a -> SrcSpanAnn' b -> SrcSpanAnn' a #

Data a => Data (SrcSpanAnn' a) 
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) -> SrcSpanAnn' a -> c (SrcSpanAnn' a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SrcSpanAnn' a) #

toConstr :: SrcSpanAnn' a -> Constr #

dataTypeOf :: SrcSpanAnn' a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> SrcSpanAnn' a -> SrcSpanAnn' a #

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

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

gmapQ :: (forall d. Data d => d -> u) -> SrcSpanAnn' a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpanAnn' a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

Semigroup an => Semigroup (SrcSpanAnn' an) 
Instance details

Defined in GHC.Parser.Annotation

NFData (SrcSpanAnn' a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: SrcSpanAnn' a -> () #

Binary a => Binary (LocatedL a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

put_ :: BinHandle -> LocatedL a -> IO () #

put :: BinHandle -> LocatedL a -> IO (Bin (LocatedL a)) #

get :: BinHandle -> IO (LocatedL a) #

Outputable a => Outputable (SrcSpanAnn' a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc #

Eq a => Eq (SrcSpanAnn' a) 
Instance details

Defined in GHC.Parser.Annotation

HasSrcSpan (SrcSpanAnn' ann) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

Methods

getLoc :: SrcSpanAnn' ann -> SrcSpan Source #

HasLoc (LocatedA a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedA a -> SrcSpan

HasLoc (LocatedN a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedN a -> SrcSpan

HiePass p => HasType (LocatedA (HsBind (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsBind (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (HsExpr (GhcPass p)))

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (Pat (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (Pat (GhcPass p)) -> HieM [HieAST Type]

ToHie (LBooleanFormula (LocatedN Name)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (ImportDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ImportDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA HsWrapper) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA HsWrapper -> HieM [HieAST Type]

ToHie (LocatedA (FixitySig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FixitySig GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FunDep GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FunDep GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsCmd (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsSplice (GhcPass p)) -> HieM [HieAST Type]

(HiePass p, Data (body (GhcPass p)), AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

ToHie (LocatedA (ConDeclField GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDeclField GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (HsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsType GhcRn) -> HieM [HieAST Type]

ToHie (LocatedC (DerivClauseTys GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedC [LocatedA (HsType GhcRn)]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedC [LocatedA (HsType GhcRn)] -> HieM [HieAST Type]

ToHie (LocatedL [LocatedA (ConDeclField GhcRn)]) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedP OverlapMode) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedP OverlapMode -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LocatedA (HsBind (GhcPass p))) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedA a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedA a) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedN a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedN a) -> HieM [HieAST Type]

ToHie (EvBindContext (LocatedA TcEvBinds)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: EvBindContext (LocatedA TcEvBinds) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA (IE GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA (IE GhcRn)) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA ModuleName) -> HieM [HieAST Type]

HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (LocatedA (Pat (GhcPass p))) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data arg, Data label) => ToHie (RContext (LocatedA (HsRecField' label arg))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LocatedA (HsRecField' label arg)) -> HieM [HieAST Type]

HiePass p => ToHie (RScoped (LocatedA (IPBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (IPBind (GhcPass p))) -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), AnnoBody p body, HiePass p) => ToHie (RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p)))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p))))) -> HieM [HieAST Type]

HiePass p => ToHie (SigContext (LocatedA (Sig (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LocatedA (Sig (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LocatedA (HsSigType GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LocatedA (HsSigType GhcRn)) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

Data flag => ToHie (TVScoped (LocatedA (HsTyVarBndr flag GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LocatedA (HsTyVarBndr flag GhcRn)) -> HieM [HieAST Type]

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

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

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

Defined in GHC.Parser.Annotation

Methods

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

HasSrcSpan (GenLocated (SrcSpanAnn' ann) a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

(HiePass p, AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Type

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Pat

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

type SrcAnn ann = SrcSpanAnn' (EpAnn ann) #

We mostly use 'SrcSpanAnn'' with an 'EpAnn''

leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering #

Strategies for ordering SrcSpans

containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool #

Tests whether the first span "contains" the other span, meaning that it covers at least as much source code. True where spans are equal.

mkGeneralSrcSpan :: FastString -> SrcSpan #

Create a "bad" SrcSpan that has not location information

mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #

Create a SrcSpan between two points in a file

isSubspanOf #

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

wiredInSrcSpan :: SrcSpan #

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

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan #

Create a SrcSpan between two points in a file

srcSpanStart :: SrcSpan -> SrcLoc #

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

srcSpanEnd :: SrcSpan -> SrcLoc #

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

srcLocCol :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc

srcLocFile :: RealSrcLoc -> FastString #

Gives the filename of the SrcLoc

srcLocLine :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc

noSrcSpan :: SrcSpan #

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

noSrcLoc :: SrcLoc #

Built-in "bad" SrcLoc values for particular locations

noLoc :: e -> Located e #

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

Finder

data FindResult #

The result of searching for an imported module.

NB: FindResult manages both user source-import lookups (which can result in Module) as well as direct imports for interfaces (which always result in InstalledModule).

Constructors

Found ModLocation Module

The module was found

NoPackage Unit

The requested unit was not found

FoundMultiple [(Module, ModuleOrigin)]

_Error_: both in multiple packages

NotFound

Not found

Fields

addBootSuffixLocnOut :: ModLocation -> ModLocation Source #

Add the -boot suffix to all output file paths associated with the module, not including the input file itself

Module and Package

data ModuleOrigin #

Given a module name, there may be multiple ways it came into scope, possibly simultaneously. This data type tracks all the possible ways it could have come into scope. Warning: don't use the record functions, they're partial!

Constructors

ModHidden

Module is hidden, and thus never will be available for import. (But maybe the user didn't realize), so we'll still keep track of these modules.)

ModUnusable UnusableUnitReason

Module is unavailable because the package is unusable.

ModOrigin

Module is public, and could have come from some places.

Fields

  • fromOrigUnit :: Maybe Bool

    Just False means that this module is in someone's exported-modules list, but that package is hidden; Just True means that it is available; Nothing means neither applies.

  • fromExposedReexport :: [UnitInfo]

    Is the module available from a reexport of an exposed package? There could be multiple.

  • fromHiddenReexport :: [UnitInfo]

    Is the module available from a reexport of a hidden package?

  • fromPackageFlag :: Bool

    Did the module export come from a package flag? (ToDo: track more information.

newtype PackageName #

Constructors

PackageName 

Instances

Instances details
Show PackageName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Uniquable PackageName 
Instance details

Defined in GHC.Unit.Info

Outputable PackageName 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageName -> SDoc #

Eq PackageName 
Instance details

Defined in GHC.Unit.Info

Linker

data Unlinked #

Objects which have yet to be linked by the compiler

Constructors

DotO FilePath

An object file (.o)

DotA FilePath

Static archive file (.a)

DotDLL FilePath

Dynamically linked library file (.so, .dll, .dylib)

BCOs CompiledByteCode [SptEntry]

A byte-code object, lives only in memory. Also carries some static pointer table entries which should be loaded along with the BCOs. See Note [Grant plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.

Instances

Instances details
NFData Unlinked Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Unlinked -> () #

Outputable Unlinked 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Unlinked -> SDoc #

data Linkable #

Information we can use to dynamically link modules into the compiler

Constructors

LM 

Fields

  • linkableTime :: UTCTime

    Time at which this linkable was built (i.e. when the bytecodes were produced, or the mod date on the files)

  • linkableModule :: Module

    The linkable module itself

  • linkableUnlinked :: [Unlinked]

    Those files and chunks of code we have yet to link.

    INVARIANT: A valid linkable always has at least one Unlinked item. If this list is empty, the Linkable represents a fake linkable, which is generated with no backend is used to avoid recompiling modules.

    ToDo: Do items get removed from this list when they get linked?

Instances

Instances details
Show Linkable Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData Linkable Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Linkable -> () #

Outputable Linkable 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Linkable -> SDoc #

Hooks

data Hooks #

data MetaRequest #

The supported metaprogramming result types

HPT

Driver-Make

data Target #

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

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc #

data TargetId #

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

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc #

Eq TargetId 
Instance details

Defined in GHC.Types.Target

GHCi

data InteractiveImport #

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
Show InteractiveImport Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Outputable InteractiveImport 
Instance details

Defined in GHC.Runtime.Context

getContext :: GhcMonad m => m [InteractiveImport] #

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.

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

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

runDecls :: GhcMonad m => String -> m [Name] #

data Warn #

A command-line warning message and the reason it arose

Constructors

Warn 

ModLocation

data ModLocation #

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.

Instances

Instances details
Show ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Outputable ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc #

ml_hs_file :: ModLocation -> Maybe FilePath #

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

ml_obj_file :: ModLocation -> 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_hi_file :: ModLocation -> 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_hie_file :: ModLocation -> FilePath #

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

DataCon

dataConExTyCoVars :: DataCon -> [TyCoVar] #

The existentially-quantified type/coercion variables of the constructor including dependent (kind-) GADT equalities

Role

data Role #

Instances

Instances details
Data Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

put_ :: BinHandle -> Role -> IO () #

put :: BinHandle -> Role -> IO (Bin Role) #

get :: BinHandle -> IO Role #

Outputable Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc #

Eq Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

Ord Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

Panic

data PlainGhcException #

This type is very similar to GhcException, but it omits the constructors that involve pretty-printing via SDoc. Due to the implementation of fromException for GhcException, this type can be caught as a GhcException.

Note that this should only be used for throwing exceptions, not for catching, as GhcException will not be converted to this type when catching.

panic :: String -> a #

Panics and asserts.

panicDoc :: String -> SDoc -> a #

Throw an exception saying "bug in GHC"

Other

data CoreModule #

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

Constructors

CoreModule 

Fields

Instances

Instances details
Show CoreModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData CoreModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: CoreModule -> () #

Outputable CoreModule 
Instance details

Defined in GHC

Methods

ppr :: CoreModule -> SDoc #

data SafeHaskellMode #

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

Instances

Instances details
Show SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

NFData SafeHaskellMode Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: SafeHaskellMode -> () #

Outputable SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

Methods

ppr :: SafeHaskellMode -> SDoc #

Eq SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

pattern GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt Source #

Util Module re-exports

class Uniquable a where #

Class of things that we can obtain a Unique from

Methods

getUnique :: a -> Unique #

Instances

Instances details
Uniquable Label 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

getUnique :: Label -> Unique #

Uniquable LocalReg 
Instance details

Defined in GHC.Cmm.Expr

Methods

getUnique :: LocalReg -> Unique #

Uniquable Class 
Instance details

Defined in GHC.Core.Class

Methods

getUnique :: Class -> Unique #

Uniquable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Uniquable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getUnique :: ConLike -> Unique #

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Uniquable PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

getUnique :: PatSyn -> Unique #

Uniquable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Uniquable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

getUnique :: TyCon -> Unique #

Uniquable FastString 
Instance details

Defined in GHC.Types.Unique

Uniquable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Uniquable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Unique -> Unique #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Uniquable PackageId 
Instance details

Defined in GHC.Unit.Info

Uniquable PackageName 
Instance details

Defined in GHC.Unit.Info

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Uniquable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: UnitId -> Unique #

Uniquable Int 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Int -> Unique #

Uniquable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique #

Uniquable unit => Uniquable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique #

IsUnitId u => Uniquable (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: GenUnit u -> Unique #

Uniquable unit => Uniquable (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Indefinite unit -> Unique #

hasKey :: Uniquable a => a -> Unique -> Bool #

data StrictnessMark #

Instances

Instances details
Outputable StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: StrictnessMark -> SDoc #

data SrcUnpackedness #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{-# UNPACK #-} specified

SrcNoUnpack

{-# NOUNPACK #-} specified

NoSrcUnpack

no unpack pragma

Instances

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

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

toConstr :: SrcUnpackedness -> Constr #

dataTypeOf :: SrcUnpackedness -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: SrcUnpackedness -> SDoc #

Eq SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

data SrcStrictness #

Source Strictness

What strictness annotation the user wrote

Constructors

SrcLazy

Lazy, ie ~

SrcStrict

Strict, ie !

NoSrcStrict

no strictness annotation

Instances

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

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

toConstr :: SrcStrictness -> Constr #

dataTypeOf :: SrcStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: SrcStrictness -> SDoc #

Eq SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

data HsSrcBang #

Haskell Source Bang

Bangs on data constructor arguments as the user wrote them in the source code.

(HsSrcBang _ SrcUnpack SrcLazy) and (HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we emit a warning (in checkValidDataCon) and treat it like (HsSrcBang _ NoSrcUnpack SrcLazy)

Instances

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

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

toConstr :: HsSrcBang -> Constr #

dataTypeOf :: HsSrcBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsSrcBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc #

data HsImplBang #

Haskell Implementation Bang

Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.

Constructors

HsLazy

Lazy field, or one with an unlifted type

HsStrict

Strict but not unpacked field

HsUnpack (Maybe Coercion)

Strict and unpacked field co :: arg-ty ~ product-ty HsBang

Instances

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

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

toConstr :: HsImplBang -> Constr #

dataTypeOf :: HsImplBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsImplBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc #

substEqSpec :: TCvSubst -> EqSpec -> EqSpec #

Substitute in an EqSpec. Precondition: if the LHS of the EqSpec is mapped in the substitution, it is mapped to a type variable, not a full type.

splitDataProductType_maybe #

Arguments

:: Type

A product type, perhaps

-> Maybe (TyCon, [Type], DataCon, [Scaled Type]) 

Extract the type constructor, type argument, data constructor and it's representation argument types from a type if it is a product type.

Precisely, we return Just for any data type that is all of:

  • Concrete (i.e. constructors visible)
  • Single-constructor
  • ... which has no existentials

Whether the type is a data type or a newtype.

specialPromotedDc :: DataCon -> Bool #

Should this DataCon be allowed in a type even without -XDataKinds? Currently, only Lifted & Unlifted

mkEqSpec :: TyVar -> Type -> EqSpec #

Make a non-dependent EqSpec

mkDataCon #

Arguments

:: Name 
-> Bool

Is the constructor declared infix?

-> TyConRepName

TyConRepName for the promoted TyCon

-> [HsSrcBang]

Strictness/unpack annotations, from user

-> [FieldLabel]

Field labels for the constructor, if it is a record, otherwise empty

-> [TyVar]

Universals.

-> [TyCoVar]

Existentials.

-> [InvisTVBinder]

User-written TyVarBinders. These must be Inferred/Specified. See Note [TyVarBinders in DataCons]

-> [EqSpec]

GADT equalities

-> KnotTied ThetaType

Theta-type occurring before the arguments proper

-> [KnotTied (Scaled Type)]

Original argument types

-> KnotTied Type

Original result type

-> RuntimeRepInfo

See comments on RuntimeRepInfo

-> KnotTied TyCon

Representation type constructor

-> ConTag

Constructor tag

-> ThetaType

The "stupid theta", context of the data declaration e.g. data Eq a => T a ...

-> Id

Worker Id

-> DataConRep

Representation

-> DataCon 

Build a new data constructor

isVanillaDataCon :: DataCon -> Bool #

Vanilla DataCons are those that are nice boring Haskell 98 constructors

isNullarySrcDataCon :: DataCon -> Bool #

Return whether there are any argument types for this DataCons original source type See Note [DataCon arities]

isNullaryRepDataCon :: DataCon -> Bool #

Return whether there are any argument types for this DataCons runtime representation type See Note [DataCon arities]

isNewDataCon :: DataCon -> Bool #

Is this the DataCon of a newtype?

filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar] #

Filter out any TyVars mentioned in an EqSpec.

eqHsBang :: HsImplBang -> HsImplBang -> Bool #

Compare strictness annotations

dataConWrapperType :: DataCon -> Type #

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.

dataConWrapId_maybe :: DataCon -> Maybe Id #

Get the Id of the DataCon wrapper: a function that wraps the "actual" constructor so it has the type visible in the source program: c.f. dataConWorkId. Returns Nothing if there is no wrapper, which occurs for an algebraic data constructor and also for a newtype (whose constructor is inlined compulsorily)

dataConUserTyVarsArePermuted :: DataCon -> Bool #

Were the type variables of the data con written in a different order than the regular order (universal tyvars followed by existential tyvars)?

This is not a cheap test, so we minimize its use in GHC as much as possible. Currently, its only call site in the GHC codebase is in mkDataConRep in MkId, and so dataConUserTyVarsArePermuted is only called at most once during a data constructor's lifetime.

dataConUnivTyVars :: DataCon -> [TyVar] #

The universally-quantified type variables of the constructor

dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar] #

Both the universal and existential type/coercion variables of the constructor

dataConTheta :: DataCon -> ThetaType #

The *full* constraints on the constructor type, including dependent GADT equalities.

dataConTag :: DataCon -> ConTag #

The tag used for ordering DataCons

dataConSrcBangs :: DataCon -> [HsSrcBang] #

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

dataConRepType :: DataCon -> Type #

The representation type of the data constructor, i.e. the sort type that will represent values of this type at runtime

dataConRepStrictness :: DataCon -> [StrictnessMark] #

Give the demands on the arguments of a Core constructor application (Con dc args)

dataConRepArity :: DataCon -> Arity #

Gives the number of actual fields in the representation of the data constructor. This may be more than appear in the source code; the extra ones are the existentially quantified dictionaries

dataConRepArgTys :: DataCon -> [Scaled Type] #

Returns the arg types of the worker, including *all* non-dependent evidence, after any flattening has been done and without substituting for any type variables

dataConOtherTheta :: DataCon -> ThetaType #

Returns constraints in the wrapper type, other than those in the dataConEqSpec

dataConOrigTyCon :: DataCon -> TyCon #

The original type constructor used in the definition of this data constructor. In case of a data family instance, that will be the family type constructor.

dataConOrigArgTys :: DataCon -> [Scaled Type] #

Returns the argument types of the wrapper, excluding all dictionary arguments and without substituting for any type variables

dataConIsInfix :: DataCon -> Bool #

Should the DataCon be presented infix?

dataConInstSig :: DataCon -> [Type] -> ([TyCoVar], ThetaType, [Type]) #

Instantiate the universal tyvars of a data con, returning ( instantiated existentials , instantiated constraints including dependent GADT equalities which are *also* listed in the instantiated existentials , instantiated args)

dataConInstArgTys #

Arguments

:: DataCon

A datacon with no existentials or equality constraints However, it can have a dcTheta (notably it can be a class dictionary, with superclasses)

-> [Type]

Instantiated at these types

-> [Scaled Type] 

Finds the instantiated types of the arguments required to construct a DataCon representation NB: these INCLUDE any dictionary args but EXCLUDE the data-declaration context, which is discarded It's all post-flattening etc; this is a representation type

dataConImplicitTyThings :: DataCon -> [TyThing] #

Find all the Ids implicitly brought into scope by the data constructor. Currently, the union of the dataConWorkId and the dataConWrapId

dataConIdentity :: DataCon -> ByteString #

The string package:module.name identifying a constructor, which is attached to its info table and used by the GHCi debugger and the heap profiler

dataConFieldType_maybe :: DataCon -> FieldLabelString -> Maybe (FieldLabel, Type) #

Extract the label and type for any given labelled field of the DataCon, or return Nothing if the field does not belong to it

dataConFieldType :: DataCon -> FieldLabelString -> Type #

Extract the type for any given labelled field of the DataCon

dataConEqSpec :: DataCon -> [EqSpec] #

Equalities derived from the result type of the data constructor, as written by the programmer in any GADT declaration. This includes *all* GADT-like equalities, including those written in by hand by the programmer.

data EqSpec #

An EqSpec is a tyvar/type pair representing an equality made in rejigging a GADT constructor

Instances

Instances details
Outputable EqSpec 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: EqSpec -> SDoc #

data DataConRep #

Data Constructor Representation See Note [Data constructor workers and wrappers]

data DataCon #

A data constructor

Instances

Instances details
Data DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: DataCon -> Constr #

dataTypeOf :: DataCon -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Outputable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc #

OutputableBndr DataCon 
Instance details

Defined in GHC.Core.DataCon

Eq DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

dataConWrapId :: DataCon -> Id #

Returns an Id which looks like the Haskell-source constructor by using the wrapper if it exists (see dataConWrapId_maybe) and failing over to the worker (see dataConWorkId)

dataConWorkId :: DataCon -> Id #

Get the Id of the DataCon worker: a function that is the "actual" constructor and has no top level binding in the program. The type may be different from the obvious one written in the source program. Panics if there is no such Id for this DataCon

dataConUserTyVars :: DataCon -> [TyVar] #

The type variables of the constructor, in the order the user wrote them

dataConUserTyVarBinders :: DataCon -> [InvisTVBinder] #

InvisTVBinders for the type variables of the constructor, in the order the user wrote them

dataConTyCon :: DataCon -> TyCon #

The type constructor that we are building via this data constructor

dataConStupidTheta :: DataCon -> ThetaType #

The "stupid theta" of the DataCon, such as data Eq a in:

data Eq a => T a = ...

dataConSourceArity :: DataCon -> Arity #

Source-level arity of the data constructor

dataConName :: DataCon -> Name #

The Name of the DataCon, giving it a unique, rooted identification

dataConInstOrigArgTys :: DataCon -> [Type] -> [Scaled Type] #

Returns just the instantiated value argument types of a DataCon, (excluding dictionary args)

dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Scaled Type], Type) #

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

1) The result of dataConUnivTyVars

2) The result of dataConExTyCoVars

3) The non-dependent GADT equalities. Dependent GADT equalities are implied by coercion variables in return value (2).

4) The other constraints of the data constructor type, excluding GADT equalities

5) The original argument types to the DataCon (i.e. before any change of the representation of the type) with linearity annotations

6) The original result type of the DataCon

dataConFieldLabels :: DataCon -> [FieldLabel] #

The labels for the fields of this particular DataCon

type ConTag = Int #

A *one-index* constructor tag

Type of the tags associated with each constructor possibility or superclass selector

fIRST_TAG :: ConTag #

Tags are allocated from here for real constructors or for superclass selectors

type FieldLabelString = FastString #

Field labels are just represented as strings; they are not necessarily unique (even within a module)

data FieldLabel #

Fields in an algebraic record type; see Note [FieldLabel].

Constructors

FieldLabel 

Fields

Instances

Instances details
Data FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

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

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

toConstr :: FieldLabel -> Constr #

dataTypeOf :: FieldLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

HasOccName FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Binary Name => Binary FieldLabel

We need the Binary Name constraint here even though there is an instance defined in GHC.Types.Name, because the we have a SOURCE import, so the instance is not in scope. And the instance cannot be added to Name.hs-boot because GHC.Utils.Binary itself depends on GHC.Types.Name.

Instance details

Defined in GHC.Types.FieldLabel

Outputable FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldLabel -> SDoc #

Eq FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

ToHie (IEContext (Located FieldLabel)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located FieldLabel) -> HieM [HieAST Type]

data InjectivityCheckResult #

Result of testing two type family equations for injectiviy.

Constructors

InjectivityAccepted

Either RHSs are distinct or unification of RHSs leads to unification of LHSs

InjectivityUnified CoAxBranch CoAxBranch

RHSs unify but LHSs don't unify under that substitution. Relevant for closed type families where equation after unification might be overlpapped (in which case it is OK if they don't unify). Constructor stores axioms after unification.

data FamInstMatch #

Constructors

FamInstMatch 

Instances

Instances details
Outputable FamInstMatch 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInstMatch -> SDoc #

type FamInstEnv = UniqDFM TyCon FamilyInstEnv #

data FamInst #

Instances

Instances details
NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc #

topReduceTyFamApp_maybe :: FamInstEnvs -> TyCon -> [Type] -> Maybe (Coercion, Type, MCoercion) #

Try to simplify a type-family application, by *one* step If topReduceTyFamApp_maybe env r F tys = Just (co, rhs, res_co) then co :: F tys ~R# rhs res_co :: typeKind(F tys) ~ typeKind(rhs) Type families and data families; always Representational role

topNormaliseType_maybe :: FamInstEnvs -> Type -> Maybe (Coercion, Type) #

Get rid of *outermost* (or toplevel) * type function redex * data family redex * newtypes returning an appropriate Representational coercion. Specifically, if topNormaliseType_maybe env ty = Just (co, ty') then (a) co :: ty ~R ty' (b) ty' is not a newtype, and is not a type-family or data-family redex

However, ty' can be something like (Maybe (F ty)), where (F ty) is a redex.

Always operates homogeneously: the returned type has the same kind as the original type, and the returned coercion is always homogeneous.

mkSingleCoAxiom :: Role -> Name -> [TyVar] -> [TyVar] -> [CoVar] -> TyCon -> [Type] -> Type -> CoAxiom Unbranched #

mkNewTypeCoAxiom :: Name -> TyCon -> [TyVar] -> [Role] -> Type -> CoAxiom Unbranched #

Create a coercion constructor (axiom) suitable for the given newtype TyCon. The Name should be that of a new coercion CoAxiom, the TyVars the arguments expected by the newtype and the type the appropriate right hand side of the newtype, with the free variables a subset of those TyVars.

mkCoAxBranch :: [TyVar] -> [TyVar] -> [CoVar] -> [Type] -> Type -> [Role] -> SrcSpan -> CoAxBranch #

lookupFamInstEnvInjectivityConflicts :: [Bool] -> FamInstEnvs -> FamInst -> [CoAxBranch] #

Check whether an open type family equation can be added to already existing instance environment without causing conflicts with supplied injectivity annotations. Returns list of conflicting axioms (type instance declarations).

injectiveBranches :: [Bool] -> CoAxBranch -> CoAxBranch -> InjectivityCheckResult #

Check whether two type family axioms don't violate injectivity annotation.

apartnessCheck #

Arguments

:: [Type]

flattened target arguments. Make sure they're flattened! See Note [Flattening type-family applications when matching instances] in GHC.Core.Unify.

-> CoAxBranch

the candidate equation we wish to use Precondition: this matches the target

-> Bool

True = equation can fire

Do an apartness check, as described in the "Closed Type Families" paper (POPL '14). This should be used when determining if an equation (CoAxBranch) of a closed type family can be used to reduce a certain target type family application.

newtype NonDetUniqFM key ele #

A wrapper around UniqFM with the sole purpose of informing call sites that the provided Foldable and Traversable instances are nondeterministic. If you use this please provide a justification why it doesn't introduce nondeterminism. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.

Constructors

NonDetUniqFM 

Fields

Instances

Instances details
Foldable (NonDetUniqFM key)

Inherently nondeterministic. If you use this please provide a justification why it doesn't introduce nondeterminism. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.

Instance details

Defined in GHC.Types.Unique.FM

Methods

fold :: Monoid m => NonDetUniqFM key m -> m #

foldMap :: Monoid m => (a -> m) -> NonDetUniqFM key a -> m #

foldMap' :: Monoid m => (a -> m) -> NonDetUniqFM key a -> m #

foldr :: (a -> b -> b) -> b -> NonDetUniqFM key a -> b #

foldr' :: (a -> b -> b) -> b -> NonDetUniqFM key a -> b #

foldl :: (b -> a -> b) -> b -> NonDetUniqFM key a -> b #

foldl' :: (b -> a -> b) -> b -> NonDetUniqFM key a -> b #

foldr1 :: (a -> a -> a) -> NonDetUniqFM key a -> a #

foldl1 :: (a -> a -> a) -> NonDetUniqFM key a -> a #

toList :: NonDetUniqFM key a -> [a] #

null :: NonDetUniqFM key a -> Bool #

length :: NonDetUniqFM key a -> Int #

elem :: Eq a => a -> NonDetUniqFM key a -> Bool #

maximum :: Ord a => NonDetUniqFM key a -> a #

minimum :: Ord a => NonDetUniqFM key a -> a #

sum :: Num a => NonDetUniqFM key a -> a #

product :: Num a => NonDetUniqFM key a -> a #

Traversable (NonDetUniqFM key)

Inherently nondeterministic. If you use this please provide a justification why it doesn't introduce nondeterminism. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.

Instance details

Defined in GHC.Types.Unique.FM

Methods

traverse :: Applicative f => (a -> f b) -> NonDetUniqFM key a -> f (NonDetUniqFM key b) #

sequenceA :: Applicative f => NonDetUniqFM key (f a) -> f (NonDetUniqFM key a) #

mapM :: Monad m => (a -> m b) -> NonDetUniqFM key a -> m (NonDetUniqFM key b) #

sequence :: Monad m => NonDetUniqFM key (m a) -> m (NonDetUniqFM key a) #

Functor (NonDetUniqFM key) 
Instance details

Defined in GHC.Types.Unique.FM

Methods

fmap :: (a -> b) -> NonDetUniqFM key a -> NonDetUniqFM key b #

(<$) :: a -> NonDetUniqFM key b -> NonDetUniqFM key a #

zipToUFM :: Uniquable key => [key] -> [elt] -> UniqFM key elt #

unsafeIntMapToUFM :: IntMap elt -> UniqFM key elt #

unsafeCastUFMKey :: UniqFM key1 elt -> UniqFM key2 elt #

Cast the key domain of a UniqFM.

As long as the domains don't overlap in their uniques this is safe.

unitUFM :: Uniquable key => key -> elt -> UniqFM key elt #

unitDirectlyUFM :: Unique -> elt -> UniqFM key elt #

ufmToIntMap :: UniqFM key elt -> IntMap elt #

sizeUFM :: UniqFM key elt -> Int #

seqEltsUFM :: ([elt] -> ()) -> UniqFM key elt -> () #

pprUniqFM :: (a -> SDoc) -> UniqFM key a -> SDoc #

pprUFMWithKeys #

Arguments

:: UniqFM key a

The things to be pretty printed

-> ([(Unique, a)] -> SDoc)

The pretty printing function to use on the elements

-> SDoc

SDoc where the things have been pretty printed

Pretty-print a non-deterministic set. The order of variables is non-deterministic and for pretty-printing that shouldn't be a problem. Having this function helps contain the non-determinism created with nonDetUFMToList.

pprUFM #

Arguments

:: UniqFM key a

The things to be pretty printed

-> ([a] -> SDoc)

The pretty printing function to use on the elements

-> SDoc

SDoc where the things have been pretty printed

Pretty-print a non-deterministic set. The order of variables is non-deterministic and for pretty-printing that shouldn't be a problem. Having this function helps contain the non-determinism created with nonDetEltsUFM.

plusUFM_CD2 :: (Maybe elta -> Maybe eltb -> eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc #

`plusUFM_CD2 f m1 m2` merges the maps using f as the combining function. Unlike plusUFM_CD, a missing value is not defaulted: it is instead passed as Nothing to f. f can never have both its arguments be Nothing.

IMPORTANT NOTE: This function strictly applies the modification function and forces the result.

`plusUFM_CD2 f m1 m2` is the same as `plusUFM_CD f (mapUFM Just m1) Nothing (mapUFM Just m2) Nothing`.

plusUFM_CD :: (elta -> eltb -> eltc) -> UniqFM key elta -> elta -> UniqFM key eltb -> eltb -> UniqFM key eltc #

`plusUFM_CD f m1 d1 m2 d2` merges the maps using f as the combinding function and d1 resp. d2 as the default value if there is no entry in m1 reps. m2. The domain is the union of the domains of m1 and m2.

IMPORTANT NOTE: This function strictly applies the modification function and forces the result unlike most the other functions in this module.

Representative example:

plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42
   == {A: f 1 42, B: f 2 3, C: f 23 4 }

plusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt #

plusUFMList :: [UniqFM key elt] -> UniqFM key elt #

plusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt #

plusMaybeUFM_C :: (elt -> elt -> Maybe elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt #

pluralUFM :: UniqFM key a -> SDoc #

Determines the pluralisation suffix appropriate for the length of a set in the same way that plural from Outputable does for lists.

partitionUFM :: (elt -> Bool) -> UniqFM key elt -> (UniqFM key elt, UniqFM key elt) #

nonDetUFMToList :: UniqFM key elt -> [(Unique, elt)] #

nonDetStrictFoldUFM_Directly :: (Unique -> elt -> a -> a) -> a -> UniqFM key elt -> a #

nonDetStrictFoldUFM :: (elt -> a -> a) -> a -> UniqFM key elt -> a #

nonDetKeysUFM :: UniqFM key elt -> [Unique] #

nonDetEltsUFM :: UniqFM key elt -> [elt] #

minusUFM :: UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1 #

mergeUFM :: (elta -> eltb -> Maybe eltc) -> (UniqFM key elta -> UniqFM key eltc) -> (UniqFM key eltb -> UniqFM key eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc #

mapUFM_Directly :: (Unique -> elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 #

mapUFM :: (elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 #

mapMaybeUFM :: (elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2 #

lookupWithDefaultUFM_Directly :: UniqFM key elt -> elt -> Unique -> elt #

lookupWithDefaultUFM :: Uniquable key => UniqFM key elt -> elt -> key -> elt #

lookupUFM_Directly :: UniqFM key elt -> Unique -> Maybe elt #

lookupUFM :: Uniquable key => UniqFM key elt -> key -> Maybe elt #

listToUFM_Directly :: [(Unique, elt)] -> UniqFM key elt #

listToUFM_C :: Uniquable key => (elt -> elt -> elt) -> [(key, elt)] -> UniqFM key elt #

listToUFM :: Uniquable key => [(key, elt)] -> UniqFM key elt #

listToIdentityUFM :: Uniquable key => [key] -> UniqFM key key #

isNullUFM :: UniqFM key elt -> Bool #

intersectUFM_C :: (elt1 -> elt2 -> elt3) -> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt3 #

intersectUFM :: UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1 #

foldUFM :: (elt -> a -> a) -> a -> UniqFM key elt -> a #

filterUFM_Directly :: (Unique -> elt -> Bool) -> UniqFM key elt -> UniqFM key elt #

filterUFM :: (elt -> Bool) -> UniqFM key elt -> UniqFM key elt #

equalKeysUFM :: UniqFM key a -> UniqFM key b -> Bool #

emptyUFM :: UniqFM key elt #

eltsUFM :: UniqFM key elt -> [elt] #

elemUFM :: Uniquable key => key -> UniqFM key elt -> Bool #

disjointUFM :: UniqFM key elt1 -> UniqFM key elt2 -> Bool #

delListFromUFM_Directly :: UniqFM key elt -> [Unique] -> UniqFM key elt #

delListFromUFM :: Uniquable key => UniqFM key elt -> [key] -> UniqFM key elt #

delFromUFM_Directly :: UniqFM key elt -> Unique -> UniqFM key elt #

delFromUFM :: Uniquable key => UniqFM key elt -> key -> UniqFM key elt #

anyUFM :: (elt -> Bool) -> UniqFM key elt -> Bool #

alterUFM :: Uniquable key => (Maybe elt -> Maybe elt) -> UniqFM key elt -> key -> UniqFM key elt #

allUFM :: (elt -> Bool) -> UniqFM key elt -> Bool #

adjustUFM_Directly :: (elt -> elt) -> UniqFM key elt -> Unique -> UniqFM key elt #

adjustUFM :: Uniquable key => (elt -> elt) -> UniqFM key elt -> key -> UniqFM key elt #

addToUFM_Directly :: UniqFM key elt -> Unique -> elt -> UniqFM key elt #

addToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM key elt -> key -> elt -> UniqFM key elt #

addToUFM_Acc :: Uniquable key => (elt -> elts -> elts) -> (elt -> elts) -> UniqFM key elts -> key -> elt -> UniqFM key elts #

addToUFM :: Uniquable key => UniqFM key elt -> key -> elt -> UniqFM key elt #

addListToUFM_Directly :: UniqFM key elt -> [(Unique, elt)] -> UniqFM key elt #

addListToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM key elt -> [(key, elt)] -> UniqFM key elt #

Add elements to the map, combining existing values with inserted ones using the given function.

addListToUFM :: Uniquable key => UniqFM key elt -> [(key, elt)] -> UniqFM key elt #

data TyCoMapper env (m :: Type -> Type) #

This describes how a "map" operation over a type/coercion should behave

Constructors

TyCoMapper 

Fields

userTypeError_maybe :: Type -> Maybe Type #

Is this type a custom user error? If so, give us the kind and the error message.

unrestricted :: a -> Scaled a #

Scale a payload by Many

tymult :: a -> Scaled a #

Scale a payload by Many; used for type arguments in core

tyConsOfType :: Type -> UniqSet TyCon #

All type constructors occurring in the type; looking through type synonyms, but not newtypes. When it finds a Class, it returns the class TyCon.

tyConArgFlags :: TyCon -> [Type] -> [ArgFlag] #

Given a TyCon and a list of argument types to which the TyCon is applied, determine each argument's visibility (Inferred, Specified, or Required).

Wrinkle: consider the following scenario:

T :: forall k. k -> k
tyConArgFlags T [forall m. m -> m -> m, S, R, Q]

After substituting, we get

T (forall m. m -> m -> m) :: (forall m. m -> m -> m) -> forall n. n -> n -> n

Thus, the first argument is invisible, S is visible, R is invisible again, and Q is visible.

tyConAppTyConPicky_maybe :: Type -> Maybe TyCon #

Retrieve the tycon heading this type, if there is one. Does not look through synonyms.

tyConAppNeedsKindSig #

Arguments

:: Bool

Should specified binders count towards injective positions in the kind of the TyCon? (If you're using visible kind applications, then you want True here.

-> TyCon 
-> Int

The number of args the TyCon is applied to.

-> Bool

Does T t_1 ... t_n need a kind signature? (Where n is the number of arguments)

Does a TyCon (that is applied to some number of arguments) need to be ascribed with an explicit kind signature to resolve ambiguity if rendered as a source-syntax type? (See Note [When does a tycon application need an explicit kind signature?] for a full explanation of what this function checks for.)

tyConAppArgs_maybe :: Type -> Maybe [Type] #

The same as snd . splitTyConApp

tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) #

Split a type constructor application into its type constructor and applied types. Note that this may fail in the case of a FunTy with an argument of unknown kind FunTy (e.g. FunTy (a :: k) Int. since the kind of a isn't of the form TYPE rep). Consequently, you may need to zonk your type before using this function.

This does *not* split types headed with (=>), as that's not a TyCon in the type-checker.

If you only need the TyCon, consider using tcTyConAppTyCon_maybe.

tcRepSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

Like tcSplitTyConApp_maybe, but doesn't look through synonyms. This assumes the synonyms have already been dealt with.

Moreover, for a FunTy, it only succeeds if the argument types have enough info to extract the runtime-rep arguments that the funTyCon requires. This will usually be true; but may be temporarily false during canonicalization: see Note [Decomposing FunTy] in GHC.Tc.Solver.Canonical and Note [The Purely Kinded Type Invariant (PKTI)] in GHC.Tc.Gen.HsType, Wrinkle around FunTy

tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type) #

Does the AppTy split as in tcSplitAppTy_maybe, but assumes that any coreView stuff is already done. Refuses to look through (c => t)

tcIsRuntimeTypeKind :: Kind -> Bool #

Is this kind equivalent to TYPE r (for some unknown r)?

This considers Constraint to be distinct from *.

tcIsLiftedTypeKind :: Kind -> Bool #

Is this kind equivalent to Type?

This considers Constraint to be distinct from Type. For a version that treats them as the same type, see isLiftedTypeKind.

tcIsBoxedTypeKind :: Kind -> Bool #

Is this kind equivalent to TYPE (BoxedRep l) for some l :: Levity?

This considers Constraint to be distinct from Type. For a version that treats them as the same type, see isLiftedTypeKind.

splitVisVarsOfType :: Type -> Pair TyCoVarSet #

Retrieve the free variables in this type, splitting them based on whether they are used visibly or invisibly. Invisible ones come first.

splitTyConApp :: Type -> (TyCon, [Type]) #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor. Panics if that is not possible. See also splitTyConApp_maybe

splitPiTys :: Type -> ([TyCoBinder], Type) #

Split off all TyCoBinders to a type, splitting both proper foralls and functions

splitPiTy_maybe :: Type -> Maybe (TyCoBinder, Type) #

Attempts to take a forall type apart; works with proper foralls and functions

splitPiTy :: Type -> (TyCoBinder, Type) #

Takes a forall type apart, or panics

splitListTyConApp_maybe :: Type -> Maybe Type #

Attempts to tease a list type apart and gives the type of the elements if successful (looks through type synonyms)

splitInvisPiTysN :: Int -> Type -> ([TyCoBinder], Type) #

Same as splitInvisPiTys, but stop when - you have found n TyCoBinders, - or you run out of invisible binders

splitInvisPiTys :: Type -> ([TyCoBinder], Type) #

Like splitPiTys, but returns only *invisible* binders, including constraints. Stops at the first visible binder.

splitFunTy_maybe :: Type -> Maybe (Mult, Type, Type) #

Attempts to extract the multiplicity, argument and result types from a type

splitFunTy :: Type -> (Mult, Type, Type) #

Attempts to extract the multiplicity, argument and result types from a type, and panics if that is not possible. See also splitFunTy_maybe

splitForAllTyVar_maybe :: Type -> Maybe (TyCoVar, Type) #

Like splitForAllTyCoVar_maybe, but only returns Just if it is a tyvar binder.

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

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.

splitForAllTyCoVar_maybe :: Type -> Maybe (TyCoVar, Type) #

Attempts to take a forall type apart, but only if it's a proper forall, with a named binder

splitForAllTyCoVarBinders :: Type -> ([TyCoVarBinder], Type) #

Like splitPiTys but split off only named binders and returns TyCoVarBinders rather than TyCoBinders

splitForAllTyCoVar :: Type -> (TyCoVar, Type) #

Take a forall type apart, or panics if that is not possible.

splitForAllReqTVBinders :: Type -> ([ReqTVBinder], Type) #

Like splitForAllTyCoVars, but only splits ForAllTys with Required type variable binders. Furthermore, each returned tyvar is annotated with ().

splitForAllInvisTVBinders :: Type -> ([InvisTVBinder], Type) #

Like splitForAllTyCoVars, but only splits ForAllTys with Invisible type variable binders. Furthermore, each returned tyvar is annotated with its Specificity.

splitForAllCoVar_maybe :: Type -> Maybe (TyCoVar, Type) #

Like splitForAllTyCoVar_maybe, but only returns Just if it is a covar binder.

splitAppTys :: Type -> (Type, [Type]) #

Recursively splits a type as far as is possible, leaving a residual type being applied to and the type arguments applied to it. Never fails, even if that means returning an empty list of type applications.

splitAppTy_maybe :: Type -> Maybe (Type, Type) #

Attempt to take a type application apart, whether it is a function, type constructor, or plain type application. Note that type family applications are NEVER unsaturated by this!

splitAppTy :: Type -> (Type, Type) #

Attempts to take a type application apart, as in splitAppTy_maybe, and panics if this is not possible

seqTypes :: [Type] -> () #

seqType :: Type -> () #

scaledSet :: Scaled a -> b -> Scaled b #

resultIsLevPoly :: Type -> Bool #

Looking past all pi-types, is the end result potentially levity polymorphic? Example: True for (forall r (a :: TYPE r). String -> a) Example: False for (forall r1 r2 (a :: TYPE r1) (b :: TYPE r2). a -> b -> Type)

repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

Like splitTyConApp_maybe, but doesn't look through synonyms. This assumes the synonyms have already been dealt with.

repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) #

Like splitAppTys, but doesn't look through type synonyms

repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) #

Does the AppTy split as in splitAppTy_maybe, but assumes that any Core view stuff is already done

repGetTyVar_maybe :: Type -> Maybe TyVar #

Attempts to obtain the type variable underlying a Type, without any expansion

pprUserTypeErrorTy :: Type -> SDoc #

Render a type corresponding to a user type error into a SDoc.

piResultTys :: HasDebugCallStack => Type -> [Type] -> Type #

(piResultTys f_ty [ty1, .., tyn]) gives the type of (f ty1 .. tyn) where f :: f_ty piResultTys is interesting because: 1. f_ty may have more for-alls than there are args 2. Less obviously, it may have fewer for-alls For case 2. think of: piResultTys (forall a.a) [forall b.b, Int] This really can happen, but only (I think) in situations involving undefined. For example: undefined :: forall a. a Term: undefined (forall b. b->b) Int This term should have type (Int -> Int), but notice that there are more type args than foralls in undefineds type.

partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a]) #

Given a list of things paired with their visibilities, partition the things into (invisible things, visible things).

nonDetCmpTc :: TyCon -> TyCon -> Ordering #

Compare two TyCons. NB: This should never see Constraint (as recognized by Kind.isConstraintKindCon) which is considered a synonym for Type in Core. See Note [Kind Constraint and kind Type] in GHC.Core.Type. See Note [nonDetCmpType nondeterminism]

newTyConInstRhs :: TyCon -> [Type] -> Type #

Unwrap one layer of newtype on a type constructor and its arguments, using an eta-reduced version of the newtype if possible. This requires tys to have at least newTyConInstArity tycon elements.

mkVisForAllTys :: [TyVar] -> Type -> Type #

Like mkForAllTys, but assumes all variables are dependent and visible

mkTyConBindersPreferAnon #

Arguments

:: [TyVar]

binders

-> TyCoVarSet

free variables of result

-> [TyConBinder] 

Given a list of type-level vars and the free vars of a result kind, makes TyCoBinders, preferring anonymous binders if the variable is, in fact, not dependent. e.g. mkTyConBindersPreferAnon (k:*),(b:k),(c:k) We want (k:*) Named, (b:k) Anon, (c:k) Anon

All non-coercion binders are visible.

mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type #

Like mkForAllTys, but assumes all variables are dependent and Inferred, a common case

mkTyCoInvForAllTy :: TyCoVar -> Type -> Type #

Make a dependent forall over an Inferred variable

mkSpecForAllTys :: [TyVar] -> Type -> Type #

Like mkForAllTys, but assumes all variables are dependent and Specified, a common case

mkSpecForAllTy :: TyVar -> Type -> Type #

Like mkForAllTy, but assumes the variable is dependent and Specified, a common case

mkScaled :: Mult -> a -> Scaled a #

mkInfForAllTy :: TyVar -> Type -> Type #

Like mkTyCoInvForAllTy, but tv should be a tyvar

mkFamilyTyConApp :: TyCon -> [Type] -> Type #

Given a family instance TyCon and its arg types, return the corresponding family type. E.g:

data family T a
data instance T (Maybe b) = MkT b

Where the instance tycon is :RTL, so:

mkFamilyTyConApp :RTL Int  =  T (Maybe Int)

mkAppTys :: Type -> [Type] -> Type #

mkAnonBinder :: AnonArgFlag -> Scaled Type -> TyCoBinder #

Make an anonymous binder

mightBeUnliftedType :: Type -> Bool #

Returns:

  • False if the type is guaranteed lifted or
  • True if it is unlifted, OR we aren't sure (e.g. in a levity-polymorphic case)

mapTyCoX :: Monad m => TyCoMapper env m -> (env -> Type -> m Type, env -> [Type] -> m [Type], env -> Coercion -> m Coercion, env -> [Coercion] -> m [Coercion]) #

mapTyCo :: Monad m => TyCoMapper () m -> (Type -> m Type, [Type] -> m [Type], Coercion -> m Coercion, [Coercion] -> m [Coercion]) #

linear :: a -> Scaled a #

Scale a payload by One

kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type #

Given a kind (TYPE rr), extract its RuntimeRep classifier rr. For example, kindRep_maybe * = Just LiftedRep Returns Nothing if the kind is not of form (TYPE rr) Treats * and Constraint as the same

kindRep :: HasDebugCallStack => Kind -> Type #

Extract the RuntimeRep classifier of a type from its kind. For example, kindRep * = LiftedRep; Panics if this is not possible. Treats * and Constraint as the same

isValidJoinPointType :: JoinArity -> Type -> Bool #

Determine whether a type could be the type of a join point of given total arity, according to the polymorphism rule. A join point cannot be polymorphic in its return type, since given join j a b x y z = e1 in e2, the types of e1 and e2 must be the same, and a and b are not in scope for e2. (See Note [The polymorphism rule of join points] in GHC.Core.) Returns False also if the type simply doesn't have enough arguments.

Note that we need to know how many arguments (type *and* value) the putative join point takes; for instance, if j :: forall a. a -> Int then j could be a binary join point returning an Int, but it could *not* be a unary join point returning a -> Int.

TODO: See Note [Excess polymorphism and join points]

isUnliftedTypeKind :: Kind -> Bool #

Returns True if the kind classifies unlifted types (like 'Int#') and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.

isUnliftedType :: HasDebugCallStack => Type -> Bool #

See Type for what an unlifted type is. Panics on levity polymorphic types; See mightBeUnliftedType for a more approximate predicate that behaves better in the presence of levity polymorphism.

isTypeLevPoly :: Type -> Bool #

Returns True if a type is levity polymorphic. Should be the same as (isKindLevPoly . typeKind) but much faster. Precondition: The type has kind (TYPE blah)

isStrictType :: HasDebugCallStack => Type -> Bool #

Computes whether an argument (or let right hand side) should be computed strictly or lazily, based only on its type. Currently, it's just isUnliftedType. Panics on levity-polymorphic types.

isStrLitTy :: Type -> Maybe FastString #

Is this a symbol literal. We also look through type synonyms.

isRuntimeRepVar :: TyVar -> Bool #

Is a tyvar of type RuntimeRep?

isRuntimeRepKindedTy :: Type -> Bool #

Is this a type of kind RuntimeRep? (e.g. LiftedRep)

isPrimitiveType :: Type -> Bool #

Returns true of types that are opaque to Haskell.

isPiTy :: Type -> Bool #

Is this a function or forall?

isNumLitTy :: Type -> Maybe Integer #

Is this a numeric literal. We also look through type synonyms.

isMultiplicityVar :: TyVar -> Bool #

Is a tyvar of type Multiplicity?

isLitTy :: Type -> Maybe TyLit #

Is this a type literal (symbol, numeric, or char)?

isLinearType :: Type -> Bool #

isLinear t returns True of a if t is a type of (curried) function where at least one argument is linear (or otherwise non-unrestricted). We use this function to check whether it is safe to eta reduce an Id in CorePrep. It is always safe to return True, because True deactivates the optimisation.

isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool #

Returns Just True if this type is surely lifted, Just False if it is surely unlifted, Nothing if we can't be sure (i.e., it is levity polymorphic), and panics if the kind does not have the shape TYPE r.

isLevityVar :: TyVar -> Bool #

Is a tyvar of type Levity?

isLevityTy :: Type -> Bool #

Is this the type Levity?

isKindLevPoly :: Kind -> Bool #

Tests whether the given kind (which should look like TYPE x) is something other than a constructor tree (that is, constructors at every node). E.g. True of TYPE k, TYPE (F Int) False of TYPE 'LiftedRep

isFunTy :: Type -> Bool #

Is this a function?

isForAllTy_ty :: Type -> Bool #

Like isForAllTy, but returns True only if it is a tyvar binder

isForAllTy_co :: Type -> Bool #

Like isForAllTy, but returns True only if it is a covar binder

isForAllTy :: Type -> Bool #

Checks whether this is a proper forall (with a named binder)

isDataFamilyAppType :: Type -> Bool #

Check whether a type is a data family type

isCoVarType :: Type -> Bool #

Does this type classify a core (unlifted) Coercion? At either role nominal or representational (t1 ~# t2) or (t1 ~R# t2) See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep

isCharLitTy :: Type -> Maybe Char #

Is this a char literal? We also look through type synonyms.

isBoxedTypeKind :: Kind -> Bool #

Returns True if the kind classifies types which are allocated on the GC'd heap and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies AddrRep or even unboxed kinds.

isBoxedType :: Type -> Bool #

See Type for what a boxed type is. Panics on levity polymorphic types; See mightBeUnliftedType for a more approximate predicate that behaves better in the presence of levity polymorphism.

isBoxedRuntimeRep :: Type -> Bool #

See isBoxedRuntimeRep_maybe.

isAnonTyCoBinder :: TyCoBinder -> Bool #

Does this binder bind a variable that is not erased? Returns True for anonymous binders.

isAlgType :: Type -> Bool #

See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors

getTyVar_maybe :: Type -> Maybe TyVar #

Attempts to obtain the type variable underlying a Type

getTyVar :: String -> Type -> TyVar #

Attempts to obtain the type variable underlying a Type, and panics with the given message if this is not a type variable type. See also getTyVar_maybe

getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type #

Extract the RuntimeRep classifier of a type. For instance, getRuntimeRep_maybe Int = LiftedRep. Returns Nothing if this is not possible.

getRuntimeRep :: HasDebugCallStack => Type -> Type #

Extract the RuntimeRep classifier of a type. For instance, getRuntimeRep_maybe Int = LiftedRep. Panics if this is not possible.

getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) #

If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind ty

funResultTy :: Type -> Type #

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

funArgTy :: Type -> Type #

Just like piResultTys but for a single argument Try not to iterate piResultTy, because it's inefficient to substitute one variable at a time; instead use 'piResultTys"

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

filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] #

Given a TyCon and a list of argument types, filter out any invisible (i.e., Inferred or Specified) arguments.

filterOutInferredTypes :: TyCon -> [Type] -> [Type] #

Given a TyCon and a list of argument types, filter out any Inferred arguments.

expandTypeSynonyms :: Type -> Type #

Expand out all type synonyms. Actually, it'd suffice to expand out just the ones that discard type variables (e.g. type Funny a = Int) But we don't know which those are currently, so we just expand all.

expandTypeSynonyms only expands out type synonyms mentioned in the type, not in the kinds of any TyCon or TyVar mentioned in the type.

Keep this synchronized with synonymTyConsOfType

eqTypes :: [Type] -> [Type] -> Bool #

Type equality on lists of types, looking through type synonyms but not newtypes.

eqTypeX :: RnEnv2 -> Type -> Type -> Bool #

Compare types with respect to a (presumably) non-empty RnEnv2.

eqType :: Type -> Type -> Bool #

Type equality on source types. Does not look through newtypes or PredTypes, but it does look through type synonyms. This first checks that the kinds of the types are equal and then checks whether the types are equal, ignoring casts and coercions. (The kind check is a recursive call, but since all kinds have type Type, there is no need to check the types of kinds.) See also Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep.

dropRuntimeRepArgs :: [Type] -> [Type] #

Drops prefix of RuntimeRep constructors in TyConApps. Useful for e.g. dropping 'LiftedRep arguments of unboxed tuple TyCon applications:

dropRuntimeRepArgs [ 'LiftedRep, 'IntRep , String, Int# ] == [String, Int#]

dropForAlls :: Type -> Type #

Drops all ForAllTys

coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type #

Get the type on the LHS of a coercion induced by a type/data family instance.

classifiesTypeWithValues :: Kind -> Bool #

Does this classify a type allowed to have values? Responds True to things like *, #, TYPE Lifted, TYPE v, Constraint.

True of any sub-kind of OpenTypeKind

buildSynTyCon #

Arguments

:: Name 
-> [KnotTied TyConBinder] 
-> Kind

result kind

-> [Role] 
-> KnotTied Type 
-> TyCon 

binderRelevantType_maybe :: TyCoBinder -> Maybe Type #

Extract a relevant type, if there is one.

applyTysX :: [TyVar] -> Type -> [Type] -> Type #

appTyArgFlags :: Type -> [Type] -> [ArgFlag] #

Given a Type and a list of argument types to which the Type is applied, determine each argument's visibility (Inferred, Specified, or Required).

Most of the time, the arguments will be Required, but not always. Consider f :: forall a. a -> Type. In f Type Bool, the first argument (Type) is Specified and the second argument (Bool) is Required. It is precisely this sort of higher-rank situation in which appTyArgFlags comes in handy, since f Type Bool would be represented in Core using AppTys. (See also #15792).

pattern One :: Mult #

pattern Many :: Mult #

funTyCon :: TyCon #

The FUN type constructor.

FUN :: forall (m :: Multiplicity) ->
       forall {rep1 :: RuntimeRep} {rep2 :: RuntimeRep}.
       TYPE rep1 -> TYPE rep2 -> *

The runtime representations quantification is left inferred. This means they cannot be specified with -XTypeApplications.

This is a deliberate choice to allow future extensions to the function arrow. To allow visible application a type synonym can be defined:

type Arr :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
            TYPE rep1 -> TYPE rep2 -> Type
type Arr = FUN 'Many

type TvSubstEnv = TyVarEnv Type #

A substitution of Types for TyVars and Kinds for KindVars

data TCvSubst #

Type & coercion substitution

The following invariants must hold of a TCvSubst:

  1. The in-scope set is needed only to guide the generation of fresh uniques
  2. In particular, the kind of the type variables in the in-scope set is not relevant
  3. The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.

Instances

Instances details
Outputable TCvSubst 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: TCvSubst -> SDoc #

zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst #

Generates the in-scope set for the TCvSubst from the types in the incoming environment. No CoVars, please!

substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type] #

Type substitution, see zipTvSubst

substTysUnchecked :: TCvSubst -> [Type] -> [Type] #

Substitute within several Types disabling the sanity checks. The problems that the sanity checks in substTys catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTysUnchecked to substTys and remove this function. Please don't use in new code.

substTys :: HasCallStack => TCvSubst -> [Type] -> [Type] #

Substitute within several Types The substitution has to satisfy the invariants described in Note [The substitution invariant].

substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type #

Type substitution, see zipTvSubst. Disables sanity checks. The problems that the sanity checks in substTy catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTyUnchecked to substTy and remove this function. Please don't use in new code.

substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type #

Type substitution, see zipTvSubst

substTyUnchecked :: TCvSubst -> Type -> Type #

Substitute within a Type disabling the sanity checks. The problems that the sanity checks in substTy catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTyUnchecked to substTy and remove this function. Please don't use in new code.

substTyAddInScope :: TCvSubst -> Type -> Type #

Substitute within a Type after adding the free variables of the type to the in-scope set. This is useful for the case when the free variables aren't already in the in-scope set or easily available. See also Note [The substitution invariant].

substTy :: HasCallStack => TCvSubst -> Type -> Type #

Substitute within a Type The substitution has to satisfy the invariants described in Note [The substitution invariant].

substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType #

Substitute within a ThetaType disabling the sanity checks. The problems that the sanity checks in substTys catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substThetaUnchecked to substTheta and remove this function. Please don't use in new code.

substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType #

Substitute within a ThetaType The substitution has to satisfy the invariants described in Note [The substitution invariant].

substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion #

Coercion substitution, see zipTvSubst. Disables sanity checks. The problems that the sanity checks in substCo catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substCoUnchecked to substCo and remove this function. Please don't use in new code.

substCoUnchecked :: TCvSubst -> Coercion -> Coercion #

Substitute within a Coercion disabling sanity checks. The problems that the sanity checks in substCo catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substCoUnchecked to substCo and remove this function. Please don't use in new code.

mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst #

Generates the in-scope set for the TCvSubst from the types in the incoming environment. No CoVars, please!

getTCvSubstRangeFVs :: TCvSubst -> VarSet #

Returns the free variables of the types in the range of a substitution as a non-deterministic set.

composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) #

(compose env1 env2)(x) is env1(env2(x)); i.e. apply env2 then env1. It assumes that both are idempotent. Typically, env1 is the refinement to a base substitution env2

composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #

Composes two substitutions, applying the second one provided first, like in function composition.

tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) #

This tidies up a type for printing in an error message, or in an interface file.

It doesn't change the uniques at all, just the print names.

tidyTypes :: TidyEnv -> [Type] -> [Type] #

Tidy a list of Types

See Note [Strictness in tidyType and friends]

tidyType :: TidyEnv -> Type -> Type #

Tidy a Type

See Note [Strictness in tidyType and friends]

tidyTopType :: Type -> Type #

Calls tidyType on a top-level type (i.e. with an empty tidying environment)

tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) #

Grabs the free type variables, tidies them and then uses tidyType to work over the type itself

tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) #

Treat a new TyCoVar as a binder, and give it a fresh tidy name using the environment if one has not already been allocated. See also tidyVarBndr

tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv #

Add the free TyVars to the env in tidy form, so that we can tidy the type they are free in

tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] #

Get the free vars of types in scoped order

tyCoVarsOfTypeWellScoped :: Type -> [TyVar] #

Get the free vars of a type in scoped order

tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet #

tyCoFVsOfType that returns free variables of a type in a deterministic set. For explanation of why using VarSet is not deterministic see Note [Deterministic FV] in GHC.Utils.FV.

tyCoFVsOfType :: Type -> FV #

The worker for tyCoFVsOfType and tyCoFVsOfTypeList. The previous implementation used unionVarSet which is O(n+m) and can make the function quadratic. It's exported, so that it can be composed with other functions that compute free variables. See Note [FV naming conventions] in GHC.Utils.FV.

Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in GHC.Utils.FV for explanation.

scopedSort :: [TyCoVar] -> [TyCoVar] #

Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]

This is a deterministic sorting operation (that is, doesn't depend on Uniques).

It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in GHC.Rename.HsType

closeOverKindsList :: [TyVar] -> [TyVar] #

Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministically ordered list.

closeOverKindsDSet :: DTyVarSet -> DTyVarSet #

Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.

data TyCoFolder env a #

Constructors

TyCoFolder 

Fields

type KnotTied ty = ty #

A type labeled KnotTied might have knot-tied tycons in it. See Note [Type checking recursive type and class declarations] in GHC.Tc.TyCl

type KindOrType = Type #

The key representation of types within the compiler

mkVisFunTys :: [Scaled Type] -> Type -> Type #

Make nested arrow types

mkVisFunTyMany :: Type -> Type -> Type infixr 3 #

Special, common, case: Arrow type with mult Many

mkVisFunTy :: Mult -> Type -> Type -> Type infixr 3 #

mkInvisFunTyMany :: Type -> Type -> Type infixr 3 #

mkInvisFunTy :: Mult -> Type -> Type -> Type infixr 3 #

mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type #

Wraps foralls over the type using the provided InvisTVBinders from left to right

mkFunTy :: AnonArgFlag -> Mult -> Type -> Type -> Type infixr 3 #

mkForAllTys :: [TyCoVarBinder] -> Type -> Type #

Wraps foralls over the type using the provided TyCoVars from left to right

isVisibleBinder :: TyCoBinder -> Bool #

Does this binder bind a visible argument?

isInvisibleBinder :: TyCoBinder -> Bool #

Does this binder bind an invisible argument?

foldTyCo :: Monoid a => TyCoFolder env a -> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a) #

isConstraintKindCon :: TyCon -> Bool #

Returns True for the TyCon of the Constraint kind.

type TyCoVarBinder = VarBndr TyCoVar ArgFlag #

Variable Binder

A TyCoVarBinder is the binder of a ForAllTy It's convenient to define this synonym here rather its natural home in GHC.Core.TyCo.Rep, because it's used in GHC.Core.DataCon.hs-boot

A TyVarBinder is a binder with only TyVar

sameVis :: ArgFlag -> ArgFlag -> Bool #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.

mkTyVarBinders :: vis -> [TyVar] -> [VarBndr TyVar vis] #

Make many named binders Input vars should be type variables

mkTyVarBinder :: vis -> TyVar -> VarBndr TyVar vis #

Make a named binder var should be a type variable

mkTyCoVarBinders :: vis -> [TyCoVar] -> [VarBndr TyCoVar vis] #

Make many named binders

mkTyCoVarBinder :: vis -> TyCoVar -> VarBndr TyCoVar vis #

Make a named binder

isVisibleArgFlag :: ArgFlag -> Bool #

Does this ArgFlag classify an argument that is written in Haskell?

isTyVar :: Var -> Bool #

Is this a type-level (i.e., computationally irrelevant, thus erasable) variable? Satisfies isTyVar = not . isId.

isInvisibleArgFlag :: ArgFlag -> Bool #

Does this ArgFlag classify an argument that is not written in Haskell?

binderVars :: [VarBndr tv argf] -> [tv] #

binderVar :: VarBndr tv argf -> tv #

binderArgFlag :: VarBndr tv argf -> argf #

tyConAppTyCon_maybe :: Type -> Maybe TyCon #

The same as fst . splitTyConApp

tcView :: Type -> Maybe Type #

Gives the typechecker view of a type. This unwraps synonyms but leaves Constraint alone. c.f. coreView, which turns Constraint into Type. Returns Nothing if no unwrapping happens. See also Note [coreView vs tcView]

tYPE :: Type -> Type #

Given a RuntimeRep, applies TYPE to it. See Note [TYPE and RuntimeRep] in GHC.Builtin.Types.Prim.

splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor

partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type]) #

Given a TyCon and a list of argument types, partition the arguments into:

  1. Inferred or Specified (i.e., invisible) arguments and
  2. Required (i.e., visible) arguments

mkTyConTy :: TyCon -> Type #

Create the plain type constructor type which has been applied to no type arguments at all.

mkTyConApp :: TyCon -> [Type] -> Type #

A key function: builds a TyConApp or FunTy as appropriate to its arguments. Applies its arguments to the constructor from left to right.

mkCastTy :: Type -> Coercion -> Type #

Make a CastTy. The Coercion must be nominal. Checks the Coercion for reflexivity, dropping it if it's reflexive. See Note [Respecting definitional equality] in GHC.Core.TyCo.Rep

mkAppTy :: Type -> Type -> Type #

Applies a type to another, as in e.g. k a

isRuntimeRepTy :: Type -> Bool #

Is this the type RuntimeRep?

isMultiplicityTy :: Type -> Bool #

Is this the type Multiplicity?

isLiftedTypeKind :: Kind -> Bool #

This version considers Constraint to be the same as *. Returns True if the argument is equivalent to Type/Constraint and False otherwise. See Note [Kind Constraint and kind Type]

coreView :: Type -> Maybe Type #

This function strips off the top layer only of a type synonym application (if any) its underlying representation type. Returns Nothing if there is nothing to look through. This function considers Constraint to be a synonym of Type.

By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing

data Type #

Instances

Instances details
Data Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData Type Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc #

Eq (DeBruijn Type) 
Instance details

Defined in GHC.Core.Map.Type

data TyCoBinder #

A TyCoBinder represents an argument to a function. TyCoBinders can be dependent (Named) or nondependent (Anon). They may also be visible or not. See Note [TyCoBinders]

Instances

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

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

toConstr :: TyCoBinder -> Constr #

dataTypeOf :: TyCoBinder -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TyCoBinder 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyCoBinder -> SDoc #

type ThetaType = [PredType] #

A collection of PredTypes

data Scaled a #

A shorthand for data with an attached Mult element (the multiplicity).

Instances

Instances details
Data a => Data (Scaled a) 
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) -> Scaled a -> c (Scaled a) #

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

toConstr :: Scaled a -> Constr #

dataTypeOf :: Scaled a -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Outputable (Scaled a) 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc #

type PredType = Type #

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 Mult = Type #

Mult is a type alias for Type.

Mult must contain Type because multiplicity variables are mere type variables (of kind Multiplicity) in Haskell. So the simplest implementation is to make Mult be Type.

Multiplicities can be formed with: - One: GHC.Types.One (= oneDataCon) - Many: GHC.Types.Many (= manyDataCon) - Multiplication: GHC.Types.MultMul (= multMulTyCon)

So that Mult feels a bit more structured, we provide pattern synonyms and smart constructors for these.

type Kind = Type #

The key type representing kinds in the compiler.

mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #

Like mkTyCoForAllTy, but does not check the occurrence of the binder See Note [Unused coercion variable in ForAllTy]

data Var #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
Data Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc #

Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

ModifyState Id 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Id -> Id -> HieState -> HieState

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

type Anno Id 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

type TyVar = Var #

Type or kind Variable

type TyCoVar = Id #

Type or Coercion Variable

data Specificity #

Whether an Invisible argument may appear in source Haskell.

Constructors

InferredSpec

the argument may not appear in source Haskell, it is only inferred.

SpecifiedSpec

the argument may appear in source Haskell, but isn't required.

Instances

Instances details
Data Specificity 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Specificity 
Instance details

Defined in GHC.Types.Var

Eq Specificity 
Instance details

Defined in GHC.Types.Var

Ord Specificity 
Instance details

Defined in GHC.Types.Var

OutputableBndrFlag Specificity p 
Instance details

Defined in GHC.Hs.Type

ReifyFlag Specificity Specificity 
Instance details

Defined in GHC.Tc.Gen.Splice

Outputable tv => Outputable (VarBndr tv Specificity) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv Specificity -> SDoc #

data ArgFlag #

Argument Flag

Is something required to appear in source Haskell (Required), permitted by request (Specified) (visible type application), or prohibited entirely from appearing in source Haskell (Inferred)? See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep

Bundled Patterns

pattern Specified :: ArgFlag 
pattern Inferred :: ArgFlag 

Instances

Instances details
Data ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: ArgFlag -> Constr #

dataTypeOf :: ArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary ArgFlag 
Instance details

Defined in GHC.Types.Var

Outputable ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ArgFlag -> SDoc #

Eq ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord ArgFlag 
Instance details

Defined in GHC.Types.Var

Outputable tv => Outputable (VarBndr tv ArgFlag) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ArgFlag -> SDoc #

data AnonArgFlag #

The non-dependent version of ArgFlag. See Note [AnonArgFlag] Appears here partly so that it's together with its friends ArgFlag and ForallVisFlag, but also because it is used in IfaceType, rather early in the compilation chain

Constructors

VisArg

Used for (->): an ordinary non-dependent arrow. The argument is visible in source code.

InvisArg

Used for (=>): a non-dependent predicate arrow. The argument is invisible in source code.

Instances

Instances details
Data AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: AnonArgFlag -> Constr #

dataTypeOf :: AnonArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Outputable AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: AnonArgFlag -> SDoc #

Eq AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Ord AnonArgFlag 
Instance details

Defined in GHC.Types.Var

data XViaStrategyPs #

Instances

Instances details
Outputable XViaStrategyPs 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: XViaStrategyPs -> SDoc #

data HsRuleAnn #

Constructors

HsRuleAnn 

Fields

Instances

Instances details
Data HsRuleAnn 
Instance details

Defined in GHC.Hs.Decls

Methods

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

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

toConstr :: HsRuleAnn -> Constr #

dataTypeOf :: HsRuleAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq HsRuleAnn 
Instance details

Defined in GHC.Hs.Decls

tyClDeclLName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyClDecl (GhcPass p) -> LocatedN (IdP (GhcPass p)) #

tcdName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyClDecl (GhcPass p) -> IdP (GhcPass p) #

roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p) #

resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a)) #

Maybe return name of the result type variable

pprTyClDeclFlavour :: forall (p :: Pass). TyClDecl (GhcPass p) -> SDoc #

partitionBindsAndSigs :: [LHsDecl GhcPs] -> (LHsBinds GhcPs, [LSig GhcPs], [LFamilyDecl GhcPs], [LTyFamInstDecl GhcPs], [LDataFamInstDecl GhcPs], [LDocDecl GhcPs]) #

Partition a list of HsDecls into function/pattern bindings, signatures, type family declarations, type family instances, and documentation comments.

Panics when given a declaration that cannot be put into any of the output groups.

The primary use of this function is to implement cvBindsAndSigs.

mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p #

Map over the via type if dealing with ViaStrategy. Otherwise, return the DerivStrategy unchanged.

hsGroupTopLevelFixitySigs :: forall (p :: Pass). HsGroup (GhcPass p) -> [LFixitySig (GhcPass p)] #

The fixity signatures for each top-level declaration and class method in an HsGroup. See Note [Top-level fixity signatures in an HsGroup]

hsDeclHasCusk :: TyClDecl GhcRn -> Bool #

Does this declaration have a complete, user-supplied kind signature? See Note [CUSKs: complete user-supplied kind signatures]

hsConDeclTheta :: forall (p :: Pass). Maybe (LHsContext (GhcPass p)) -> [LHsType (GhcPass p)] #

getRecConArgs_maybe :: ConDecl GhcRn -> Maybe (LocatedL [LConDeclField GhcRn]) #

Return Just fields if a data constructor declaration uses record syntax (i.e., RecCon), where fields are the field selectors. Otherwise, return Nothing.

foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r #

Eliminate a DerivStrategy.

flattenRuleDecls :: forall (p :: Pass). [LRuleDecls (GhcPass p)] -> [LRuleDecl (GhcPass p)] #

familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p) #

familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> XRec (GhcPass p) (IdP (GhcPass p)) #

emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p) #

emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p) #

appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p) #

data WarnDecls pass #

Warning pragma Declarations

Constructors

Warnings 

Fields

XWarnDecls !(XXWarnDecls pass) 

Instances

Instances details
ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

type Anno (WarnDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data WarnDecl pass #

Warning pragma Declaration

Constructors

Warning (XWarning pass) [LIdP pass] WarningTxt 
XWarnDecl !(XXWarnDecl pass) 

Instances

Instances details
ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

type Anno (WarnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type TyFamInstEqn pass = FamEqn pass (LHsType pass) #

Type Family Instance Equation

data TyFamInstDecl pass #

Type Family Instance Declaration

Instances

Instances details
ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (TyFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type TyFamDefltDecl = TyFamInstDecl #

Type family default declarations. A convenient synonym for TyFamInstDecl. See Note [Type family instance declarations in HsSyn].

data TyClGroup pass #

Type or Class Group

Instances

Instances details
ToHie (TyClGroup GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TyClGroup GhcRn -> HieM [HieAST Type]

data TyClDecl pass #

A type or class declaration.

Constructors

FamDecl
type/data family T :: *->*

Fields

SynDecl

type declaration

Fields

DataDecl

data declaration

Fields

ClassDecl 

Fields

XTyClDecl !(XXTyClDecl pass) 

Instances

Instances details
ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

type Anno (TyClDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data StandaloneKindSig pass #

Instances

Instances details
ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (StandaloneKindSig GhcRn) 
Instance details

Defined in Compat.HieAst

type Anno (StandaloneKindSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data SpliceDecl p #

Splice Declaration

Instances

Instances details
ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

type Anno (SpliceDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleDecls pass #

Rule Declarations

Constructors

HsRules 

Fields

XRuleDecls !(XXRuleDecls pass) 

Instances

Instances details
ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

type Anno (RuleDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleDecl pass #

Rule Declaration

Constructors

HsRule 

Fields

XRuleDecl !(XXRuleDecl pass) 

Instances

Instances details
ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

type Anno (RuleDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleBndr pass #

Rule Binder

Instances

Instances details
ToHie (RScoped (Located (RuleBndr GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (RuleBndr GhcRn)) -> HieM [HieAST Type]

type Anno (RuleBndr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RoleAnnotDecl pass #

Role Annotation Declaration

Instances

Instances details
ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (RoleAnnotDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data NewOrData #

Constructors

NewType
newtype Blah ...
DataType
data Blah ...

Instances

Instances details
Data NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: NewOrData -> Constr #

dataTypeOf :: NewOrData -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: NewOrData -> SDoc #

Eq NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

type LWarnDecls pass = XRec pass (WarnDecls pass) #

Located Warning Declarations

type LWarnDecl pass = XRec pass (WarnDecl pass) #

Located Warning pragma Declaration

type LTyFamInstEqn pass #

Arguments

 = XRec pass (TyFamInstEqn pass)

May have AnnKeywordId : AnnSemi when in a list

Located Type Family Instance Equation

type LTyFamInstDecl pass = XRec pass (TyFamInstDecl pass) #

Located Type Family Instance Declaration

type LTyFamDefltDecl pass = XRec pass (TyFamDefltDecl pass) #

Located type family default declarations.

type LTyClDecl pass = XRec pass (TyClDecl pass) #

Located Declaration of a Type or Class

type LStandaloneKindSig pass = XRec pass (StandaloneKindSig pass) #

Located Standalone Kind Signature

type LSpliceDecl pass = XRec pass (SpliceDecl pass) #

Located Splice Declaration

type LRuleDecls pass = XRec pass (RuleDecls pass) #

Located Rule Declarations

type LRuleDecl pass = XRec pass (RuleDecl pass) #

Located Rule Declaration

type LRuleBndr pass = XRec pass (RuleBndr pass) #

Located Rule Binder

type LRoleAnnotDecl pass = XRec pass (RoleAnnotDecl pass) #

Located Role Annotation Declaration

type LInstDecl pass = XRec pass (InstDecl pass) #

Located Instance Declaration

type LInjectivityAnn pass = XRec pass (InjectivityAnn pass) #

Located Injectivity Annotation

type LHsFunDep pass = XRec pass (FunDep pass) #

type LHsDerivingClause pass = XRec pass (HsDerivingClause pass) #

type LHsDecl p #

Arguments

 = XRec p (HsDecl p)

When in a list this may have

type LForeignDecl pass = XRec pass (ForeignDecl pass) #

Located Foreign Declaration

type LFamilyResultSig pass = XRec pass (FamilyResultSig pass) #

Located type Family Result Signature

type LFamilyDecl pass = XRec pass (FamilyDecl pass) #

Located type Family Declaration

type LDocDecl pass = XRec pass DocDecl #

Located Documentation comment Declaration

type LDerivDecl pass = XRec pass (DerivDecl pass) #

Located stand-alone 'deriving instance' declaration

type LDerivClauseTys pass = XRec pass (DerivClauseTys pass) #

type LDefaultDecl pass = XRec pass (DefaultDecl pass) #

Located Default Declaration

type LDataFamInstDecl pass = XRec pass (DataFamInstDecl pass) #

Located Data Family Instance Declaration

type LConDecl pass #

Arguments

 = XRec pass (ConDecl pass)

May have AnnKeywordId : AnnSemi when in a GADT constructor list

Located data Constructor Declaration

type LClsInstDecl pass = XRec pass (ClsInstDecl pass) #

Located Class Instance Declaration

type LAnnDecl pass = XRec pass (AnnDecl pass) #

Located Annotation Declaration

data InstDecl pass #

Instance Declaration

Instances

Instances details
ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

type Anno (InstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data InjectivityAnn pass #

If the user supplied an injectivity annotation it is represented using InjectivityAnn. At the moment this is a single injectivity condition - see Note [Injectivity annotation]. `Located name` stores the LHS of injectivity condition. `[Located name]` stores the RHS of injectivity condition. Example:

type family Foo a b c = r | r -> a c where ...

This will be represented as "InjectivityAnn r [a, c]"

Instances

Instances details
ToHie (Located (InjectivityAnn GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (InjectivityAnn (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type HsTyPats pass = [LHsTypeArg pass] #

Haskell Type Patterns

data HsRuleRn #

Constructors

HsRuleRn NameSet NameSet 

Instances

Instances details
Data HsRuleRn 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: HsRuleRn -> Constr #

dataTypeOf :: HsRuleRn -> DataType #

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

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

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

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

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

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

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

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

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

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

data HsGroup p #

Haskell Group

A HsDecl is categorised into a HsGroup before being fed to the renamer.

data HsDerivingClause pass #

A single deriving clause of a data declaration.

Constructors

HsDerivingClause 

Fields

XHsDerivingClause !(XXHsDerivingClause pass) 

Instances

Instances details
ToHie (Located (HsDerivingClause GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (Located [Located (HsDerivingClause GhcRn)]) 
Instance details

Defined in Compat.HieAst

type Anno (HsDerivingClause (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type HsDeriving pass #

Arguments

 = [LHsDerivingClause pass]

The optional deriving clauses of a data declaration. Clauses is plural because one can specify multiple deriving clauses using the -XDerivingStrategies language extension.

The list of LHsDerivingClauses corresponds to exactly what the user requested to derive, in order. If no deriving clauses were specified, the list is empty.

Haskell Deriving clause

data HsDecl p #

A Haskell Declaration

Constructors

TyClD (XTyClD p) (TyClDecl p)

Type or Class Declaration

InstD (XInstD p) (InstDecl p)

Instance declaration

DerivD (XDerivD p) (DerivDecl p)

Deriving declaration

ValD (XValD p) (HsBind p)

Value declaration

SigD (XSigD p) (Sig p)

Signature declaration

KindSigD (XKindSigD p) (StandaloneKindSig p)

Standalone kind signature

DefD (XDefD p) (DefaultDecl p)

'default' declaration

ForD (XForD p) (ForeignDecl p)

Foreign declaration

WarningD (XWarningD p) (WarnDecls p)

Warning declaration

AnnD (XAnnD p) (AnnDecl p)

Annotation declaration

RuleD (XRuleD p) (RuleDecls p)

Rule declaration

SpliceD (XSpliceD p) (SpliceDecl p)

Splice declaration (Includes quasi-quotes)

DocD (XDocD p) DocDecl

Documentation comment declaration

RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p)

Role annotation declaration

XHsDecl !(XXHsDecl p) 

Instances

Instances details
type Anno (HsDecl (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

data HsDataDefn pass #

Haskell Data type Definition

Constructors

HsDataDefn

Declares a data type or newtype, giving its constructors data/newtype T a = constrs data/newtype instance T [a] = constrs

Fields

XHsDataDefn !(XXHsDataDefn pass) 

Instances

Instances details
HasLoc (HsDataDefn GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (HsDataDefn GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsDataDefn GhcRn -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (HsDataDefn GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (HsDataDefn GhcRn)) -> HieM [HieAST Type]

type HsConDeclH98Details pass = HsConDetails Void (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass]) #

The arguments in a Haskell98-style data constructor.

data HsConDeclGADTDetails pass #

The arguments in a GADT constructor. Unlike Haskell98-style constructors, GADT constructors cannot be declared with infix syntax. As a result, we do not use HsConDetails here, as InfixCon would be an unrepresentable state. (There is a notion of infix GADT constructors for the purposes of derived Show instances—see Note [Infix GADT constructors] in GHC.Tc.TyCl—but that is an orthogonal concern.)

Constructors

PrefixConGADT [HsScaled pass (LBangType pass)] 
RecConGADT (XRec pass [LConDeclField pass]) 

Instances

Instances details
ToHie (HsConDeclGADTDetails GhcRn) 
Instance details

Defined in Compat.HieAst

pattern XFunDep :: !(XXFunDep pass) -> FunDep pass #

data ForeignImport #

Instances

Instances details
Data ForeignImport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: ForeignImport -> Constr #

dataTypeOf :: ForeignImport -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignImport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: ForeignImport -> SDoc #

ToHie ForeignImport 
Instance details

Defined in Compat.HieAst

Methods

toHie :: ForeignImport -> HieM [HieAST Type]

data ForeignExport #

Instances

Instances details
Data ForeignExport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: ForeignExport -> Constr #

dataTypeOf :: ForeignExport -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignExport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: ForeignExport -> SDoc #

ToHie ForeignExport 
Instance details

Defined in Compat.HieAst

Methods

toHie :: ForeignExport -> HieM [HieAST Type]

data ForeignDecl pass #

Foreign Declaration

Instances

Instances details
ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

type Anno (ForeignDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamilyResultSig pass #

type Family Result Signature

Instances

Instances details
ToHie (RScoped (Located (FamilyResultSig GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (FamilyResultSig GhcRn)) -> HieM [HieAST Type]

type Anno (FamilyResultSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamilyInfo pass #

Constructors

DataFamily 
OpenTypeFamily 
ClosedTypeFamily (Maybe [LTyFamInstEqn pass])

Nothing if we're in an hs-boot file and the user said "type family Foo x where .."

Instances

Instances details
Outputable (FamilyInfo pass) 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: FamilyInfo pass -> SDoc #

ToHie (FamilyInfo GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: FamilyInfo GhcRn -> HieM [HieAST Type]

data FamilyDecl pass #

type Family Declaration

Instances

Instances details
ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

type Anno (FamilyDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamEqn pass rhs #

Family Equation

One equation in a type family instance declaration, data family instance declaration, or type family default. See Note [Type family instance declarations in HsSyn] See Note [Family instance declaration binders]

Constructors

FamEqn 

Fields

XFamEqn !(XXFamEqn pass rhs) 

Instances

Instances details
ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (HsDataDefn GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (HsDataDefn GhcRn)) -> HieM [HieAST Type]

(HasLoc a, HiePass p) => HasLoc (FamEqn (GhcPass p) a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: FamEqn (GhcPass p) a -> SrcSpan

(ToHie rhs, HasLoc rhs) => ToHie (FamEqn GhcRn rhs) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: FamEqn GhcRn rhs -> HieM [HieAST Type]

type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

data DocDecl #

Documentation comment Declaration

Instances

Instances details
Data DocDecl 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: DocDecl -> Constr #

dataTypeOf :: DocDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable DocDecl 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: DocDecl -> SDoc #

type Anno DocDecl 
Instance details

Defined in GHC.Hs.Decls

data DerivStrategy pass #

Which technique the user explicitly requested when deriving an instance.

Constructors

StockStrategy (XStockStrategy pass)

GHC's "standard" strategy, which is to implement a custom instance for the data type. This only works for certain types that GHC knows about (e.g., Eq, Show, Functor when -XDeriveFunctor is enabled, etc.)

AnyclassStrategy (XAnyClassStrategy pass)
-XDeriveAnyClass
NewtypeStrategy (XNewtypeStrategy pass)
-XGeneralizedNewtypeDeriving
ViaStrategy (XViaStrategy pass)
-XDerivingVia

Instances

Instances details
ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

type Anno (DerivStrategy (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DerivDecl pass #

Stand-alone 'deriving instance' declaration

Constructors

DerivDecl 

Fields

XDerivDecl !(XXDerivDecl pass) 

Instances

Instances details
ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

type Anno (DerivDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DerivClauseTys pass #

The types mentioned in a single deriving clause. This can come in two forms, DctSingle or DctMulti, depending on whether the types are surrounded by enclosing parentheses or not. These parentheses are semantically different than HsParTy. For example, deriving () means "derive zero classes" rather than "derive an instance of the 0-tuple".

DerivClauseTys use LHsSigType because deriving clauses can mention type variables that aren't bound by the datatype, e.g.

data T b = ... deriving (C [a])

should produce a derived instance for C [a] (T b).

Constructors

DctSingle (XDctSingle pass) (LHsSigType pass)

A deriving clause with a single type. Moreover, that type can only be a type constructor without any arguments.

Example: deriving Eq

DctMulti (XDctMulti pass) [LHsSigType pass]

A deriving clause with a comma-separated list of types, surrounded by enclosing parentheses.

Example: deriving (Eq, C a)

XDerivClauseTys !(XXDerivClauseTys pass) 

Instances

Instances details
ToHie (LocatedC (DerivClauseTys GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (DerivClauseTys (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

data DefaultDecl pass #

Default Declaration

Instances

Instances details
ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

type Anno (DefaultDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

newtype DataFamInstDecl pass #

Data Family Instance Declaration

Instances

Instances details
ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (DataFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DataDeclRn #

Constructors

DataDeclRn 

Fields

Instances

Instances details
Data DataDeclRn 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: DataDeclRn -> Constr #

dataTypeOf :: DataDeclRn -> DataType #

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

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

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

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

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

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

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

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

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

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

data ConDecl pass #

data T b = forall a. Eq a => MkT a b
  MkT :: forall b a. Eq a => MkT a b

data T b where
     MkT1 :: Int -> T Int

data T = Int MkT Int
       | MkT2

data T a where
     Int MkT Int :: T Int

data Constructor Declaration

Constructors

ConDeclGADT 

Fields

ConDeclH98 

Fields

XConDecl !(XXConDecl pass) 

Instances

Instances details
ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

type Anno (ConDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data ClsInstDecl pass #

Class Instance Declaration

Instances

Instances details
ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

type Anno (ClsInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data CImportSpec #

Instances

Instances details
Data CImportSpec 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: CImportSpec -> Constr #

dataTypeOf :: CImportSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnProvenance pass #

Annotation Provenance

Instances

Instances details
ToHie (AnnProvenance GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: AnnProvenance GhcRn -> HieM [HieAST Type]

data AnnDecl pass #

Annotation Declaration

Instances

Instances details
ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

type Anno (AnnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

isTypeFamilyDecl :: TyClDecl pass -> Bool #

type family declaration

isSynDecl :: TyClDecl pass -> Bool #

type or type instance declaration

isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool #

open type family info

isFamilyDecl :: TyClDecl pass -> Bool #

type/data family declaration

isDataFamilyDecl :: TyClDecl pass -> Bool #

data family declaration

isDataDecl :: TyClDecl pass -> Bool #

True = argument is a data/newtype declaration.

isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool #

closed type family info

isClassDecl :: TyClDecl pass -> Bool #

type class

derivStrategyName :: DerivStrategy a -> SDoc #

A short description of a DerivStrategy'.

countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int) #

data SpliceExplicitFlag #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances

Instances details
Data SpliceExplicitFlag 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

toConstr :: SpliceExplicitFlag -> Constr #

dataTypeOf :: SpliceExplicitFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

module GHC.Hs.Doc

module GHC.Hs.Pat

class UnXRec p => CollectPass p where #

This class specifies how to collect variable identifiers from extension patterns in the given pass. Consumers of the GHC API that define their own passes should feel free to implement instances in order to make use of functions which depend on it.

In particular, Haddock already makes use of this, with an instance for its DocNameI pass so that it can reuse the code in GHC for collecting binders.

Methods

collectXXPat :: Proxy p -> CollectFlag p -> XXPat p -> [IdP p] -> [IdP p] #

Instances

Instances details
IsPass p => CollectPass (GhcPass p) 
Instance details

Defined in GHC.Hs.Utils

Methods

collectXXPat :: Proxy (GhcPass p) -> CollectFlag (GhcPass p) -> XXPat (GhcPass p) -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] #

data CollectFlag p where #

Indicate if evidence binders have to be collected.

This type is used as a boolean (should we collect evidence binders or not?) but also to pass an evidence that the AST has been typechecked when we do want to collect evidence binders, otherwise these binders are not available.

See Note [Dictionary binders in ConPatOut]

Constructors

CollNoDictBinders :: forall p. CollectFlag p

Don't collect evidence binders

CollWithDictBinders :: CollectFlag (GhcPass 'Typechecked)

Collect evidence binders

unguardedRHS :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan => EpAnn GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) -> [LGRHS (GhcPass p) (LocatedA (body (GhcPass p)))] #

unguardedGRHSs :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan => SrcSpan -> LocatedA (body (GhcPass p)) -> EpAnn GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) #

spanHsLocaLBinds :: forall (p :: Pass). Data (HsLocalBinds (GhcPass p)) => HsLocalBinds (GhcPass p) -> SrcSpan #

Return the SrcSpan encompassing the contents of any enclosed binds

nl_HsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> HsExpr (GhcPass p) #

nlWildPatName :: LPat GhcRn #

Wildcard pattern - after renaming

nlWildPat :: LPat GhcPs #

Wildcard pattern - after parsing

nlVarPat :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LPat (GhcPass p) #

nlParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name) #

nlHsVarApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [IdP (GhcPass p)] -> LHsExpr (GhcPass p) #

nlHsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LHsExpr (GhcPass p) #

nlHsTyVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LHsType (GhcPass p) #

nlHsTyConApp :: forall (p :: Pass) a. IsSrcSpanAnn p a => LexicalFixity -> IdP (GhcPass p) -> [LHsTypeArg (GhcPass p)] -> LHsType (GhcPass p) #

nlHsParTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) #

nlHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

nlHsLit :: forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p) #

nlHsIntLit :: forall (p :: Pass). Integer -> LHsExpr (GhcPass p) #

nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

nlHsApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [LHsExpr (GhcPass p)] -> LHsExpr (GhcPass p) #

nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p) #

nlHsApp :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

mkVarBind :: forall (p :: Pass). IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p) #

mkTopFunBind :: Origin -> LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn #

In Name-land, with empty bind_fvs

mkSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan) => HsMatchContext (NoGhcTc (GhcPass p)) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) #

mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs #

Convenience function using mkFunBind. This is for generated bindings only, do not use for user-written code.

mkRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => EpAnn AnnList -> LocatedL [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR #

mkPrefixFunRhs :: LIdP p -> HsMatchContext p #

Make a prefix, non-strict function HsMatchContext

mkParPat :: forall (p :: Pass). IsPass p => LPat (GhcPass p) -> LPat (GhcPass p) #

mkMatchGroup :: forall (p :: Pass) body. AnnoBody p body => Origin -> LocatedL [LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))] -> MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) #

mkMatch :: forall (p :: Pass). IsPass p => HsMatchContext (NoGhcTc (GhcPass p)) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> HsLocalBinds (GhcPass p) -> LMatch (GhcPass p) (LHsExpr (GhcPass p)) #

mkLastStmt :: forall (idR :: Pass) bodyR (idL :: Pass). IsPass idR => LocatedA (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (LocatedA (bodyR (GhcPass idR))) #

mkLHsVarTuple :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) #

mkLHsTupleExpr :: forall (p :: Pass). [LHsExpr (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) #

mkLHsPar :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

Wrap in parens if hsExprNeedsParens appPrec says it needs them So f x becomes (f x), but 3 stays as 3.

mkHsWrap :: HsWrapper -> HsExpr GhcTc -> HsExpr GhcTc #

Avoid HsWrap co1 (HsWrap co2 _) and HsWrap co1 (HsPar _ _) See Note [Detecting forced eta expansion] in GHC.HsToCore.Expr

mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p) #

mkHsString :: forall (p :: Pass). String -> HsLit (GhcPass p) #

mkHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

e => (e)

mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs #

A useful function for building OpApps. The operator is always a variable, and we don't know the fixity yet.

mkHsLam :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ NoExtField) => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #

mkHsCharPrimLit :: forall (p :: Pass). Char -> HsLit (GhcPass p) #

mkHsCaseAlt :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan, Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA) => LPat (GhcPass p) -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) #

A simple case alternative with a single pattern, no binds, no guards; pre-typechecking

mkHsAppsWith :: forall (id :: Pass). (LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> HsExpr (GhcPass id) -> LHsExpr (GhcPass id)) -> LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #

mkHsApps :: forall (id :: Pass). LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #

mkHsAppWith :: forall (id :: Pass). (LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> HsExpr (GhcPass id) -> LHsExpr (GhcPass id)) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

mkFunBind :: Origin -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs #

Not infix, with place holders for coercion and free vars

mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs] #

Convert TypeSig to ClassOpSig. The former is what is parsed, but the latter is what we need in class/instance declarations

mkChunkified #

Arguments

:: ([a] -> a)

"Small" constructor function, of maximum input arity mAX_TUPLE_SIZE

-> [a]

Possible "big" list of things to construct from

-> a

Constructed thing made possible by recursive decomposition

Lifts a "small" constructor into a "big" constructor by recursive decomposition

mkBodyStmt :: forall bodyR (idL :: Pass). LocatedA (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (LocatedA (bodyR GhcPs)) #

mkBigLHsVarTup :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) #

The Big equivalents for the source tuple expressions

mkBigLHsVarPatTup :: [IdP GhcRn] -> LPat GhcRn #

The Big equivalents for the source tuple patterns

mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> XExplicitTuple (GhcPass id) -> LHsExpr (GhcPass id) #

lStmtsImplicits :: forall (idR :: Pass) (body :: Type -> Type). [LStmtLR GhcRn (GhcPass idR) (LocatedA (body (GhcPass idR)))] -> [(SrcSpan, [Name])] #

isUnliftedHsBind :: HsBind GhcTc -> Bool #

Should we treat this as an unlifted bind? This will be true for any bind that binds an unlifted variable, but we must be careful around AbsBinds. See Note [Unlifted id check in isUnliftedHsBind]. For usage information, see Note [Strict binds checks] is GHC.HsToCore.Binds.

isInfixFunBind :: forall id1 id2. UnXRec id2 => HsBindLR id1 id2 -> Bool #

If any of the matches in the FunBind are infix, the FunBind is considered infix.

isBangedHsBind :: HsBind GhcTc -> Bool #

Is a binding a strict variable or pattern bind (e.g. !x = ...)?

hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])] #

hsPatSynSelectors :: forall (p :: Pass). IsPass p => HsValBinds (GhcPass p) -> [FieldOcc (GhcPass p)] #

Collects record pattern-synonym selectors only; the pattern synonym names are collected by collectHsValBinders.

hsLTyClDeclBinders :: forall (p :: Pass). IsPass p => LocatedA (TyClDecl (GhcPass p)) -> ([LocatedA (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #

Returns all the binding names of the decl. The first one is guaranteed to be the name of the decl. The first component represents all binding names except record fields; the second represents field occurrences. For record fields mentioned in multiple constructors, the SrcLoc will be from the first occurrence.

Each returned (Located name) has a SrcSpan for the whole declaration. See Note [SrcSpan for binders]

hsForeignDeclsBinders :: forall (p :: Pass) a. (UnXRec (GhcPass p), IsSrcSpanAnn p a) => [LForeignDecl (GhcPass p)] -> [LIdP (GhcPass p)] #

See Note [SrcSpan for binders]

hsDataFamInstBinders :: forall (p :: Pass). IsPass p => DataFamInstDecl (GhcPass p) -> ([LocatedA (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #

the SrcLoc returned are for the whole declarations, not just the names

getPatSynBinds :: UnXRec id => [(RecFlag, LHsBinds id)] -> [PatSynBind id id] #

emptyRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => StmtLR (GhcPass idL) GhcPs bodyR #

collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #

collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #

collectMethodBinders :: UnXRec idL => LHsBindsLR idL idR -> [LIdP idL] #

Used exclusively for the bindings of an instance decl which are all FunBinds

collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #

collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #

collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #

collectHsValBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #

collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #

Collect Id binders only, or Ids + pattern synonyms, respectively

collectHsBindListBinders :: CollectPass p => CollectFlag p -> [LHsBindLR p idR] -> [IdP p] #

Same as collectHsBindsBinders, but works over a list of bindings

collectHsBindBinders :: CollectPass p => CollectFlag p -> HsBindLR p idR -> [IdP p] #

Collect both Ids and pattern-synonym binders

chunkify :: [a] -> [[a]] #

Split a list into lists that are small enough to have a corresponding tuple arity. The sub-lists of the result all have length <= mAX_TUPLE_SIZE But there may be more than mAX_TUPLE_SIZE sub-lists

mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

mkHsAppKindTy :: forall (p :: Pass). XAppKindTy (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

data UntypedSpliceFlavour #

Instances

Instances details
Data UntypedSpliceFlavour 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: UntypedSpliceFlavour -> Constr #

dataTypeOf :: UntypedSpliceFlavour -> DataType #

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

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

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

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

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

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

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

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

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

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

data TransForm #

Constructors

ThenForm 
GroupForm 

Instances

Instances details
Data TransForm 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: TransForm -> Constr #

dataTypeOf :: TransForm -> DataType #

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

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

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

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

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

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

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

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

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

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

newtype ThModFinalizers #

Finalizers produced by a splice with addModFinalizer

See Note [Delaying modFinalizers in untyped splices] in GHC.Rename.Splice. For how this is used.

Constructors

ThModFinalizers [ForeignRef (Q ())] 

Instances

Instances details
Data ThModFinalizers 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: ThModFinalizers -> Constr #

dataTypeOf :: ThModFinalizers -> DataType #

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

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

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

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

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

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

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

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

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

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

data StmtLR idL idR body #

Exact print annotations when in qualifier lists or guards - AnnKeywordId : AnnVbar, AnnComma,AnnThen, AnnBy,AnnBy, AnnGroup,AnnUsing

Constructors

LastStmt (XLastStmt idL idR body) body (Maybe Bool) (SyntaxExpr idR) 
BindStmt 

Fields

  • (XBindStmt idL idR body)

    Post renaming has optional fail and bind / (>>=) operator. Post typechecking, also has multiplicity of the argument and the result type of the function passed to bind; that is, (P, S) in (>>=) :: Q -> (R # P -> S) -> T See Note [The type of bind in Stmts]

  • (LPat idL)
     
  • body
     
ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR))

ApplicativeStmt represents an applicative expression built with <$> and <*>. It is generated by the renamer, and is desugared into the appropriate applicative expression by the desugarer, but it is intended to be invisible in error messages.

For full details, see Note [ApplicativeDo] in GHC.Rename.Expr

BodyStmt (XBodyStmt idL idR body) body (SyntaxExpr idR) (SyntaxExpr idR) 
LetStmt (XLetStmt idL idR body) (HsLocalBindsLR idL idR)
ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR) 
TransStmt 

Fields

RecStmt

Fields

XStmtLR !(XXStmtLR idL idR body) 

Instances

Instances details
(ToHie (LocatedA (body (GhcPass p))), AnnoBody p body, HiePass p) => ToHie (RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p)))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p))))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

type Stmt id body = StmtLR id id body #

do block Statement

data SpliceDecoration #

A splice can appear with various decorations wrapped around it. This data type captures explicitly how it was originally written, for use in the pretty printer.

Constructors

DollarSplice

$splice or $$splice

BareSplice

bare splice

Instances

Instances details
Data SpliceDecoration 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: SpliceDecoration -> Constr #

dataTypeOf :: SpliceDecoration -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpliceDecoration 
Instance details

Defined in Language.Haskell.Syntax.Expr

Outputable SpliceDecoration 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

ppr :: SpliceDecoration -> SDoc #

Eq SpliceDecoration 
Instance details

Defined in Language.Haskell.Syntax.Expr

type RecUpdProj p = RecProj p (LHsExpr p) #

type RecProj p arg = HsRecField' (FieldLabelStrings p) arg #

type family PendingTcSplice' p #

Instances

Instances details
type PendingTcSplice' (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family PendingRnSplice' p #

Instances

Instances details
type PendingRnSplice' (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

data ParStmtBlock idL idR #

Parenthesised Statement Block

Constructors

ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR) 
XParStmtBlock !(XXParStmtBlock idL idR) 

data MatchGroupTc #

Constructors

MatchGroupTc 

Instances

Instances details
Data MatchGroupTc 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: MatchGroupTc -> Constr #

dataTypeOf :: MatchGroupTc -> DataType #

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

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

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

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

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

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

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

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

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

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

data Match p body #

Constructors

Match 

Fields

XMatch !(XXMatch p body) 

Instances

Instances details
(HiePass p, Data (body (GhcPass p)), AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

type LStmtLR idL idR body = XRec idL (StmtLR idL idR body) #

Located Statement with separate Left and Right id's

type LStmt id body = XRec id (StmtLR id id body) #

Located do block Statement

type LMatch id body = XRec id (Match id body) #

Located Match

May have AnnKeywordId : AnnSemi when in a list

type LHsTupArg id = XRec id (HsTupArg id) #

Located Haskell Tuple Argument

HsTupArg is used for tuple sections (,a,) is represented by ExplicitTuple [Missing ty1, Present a, Missing ty3] Which in turn stands for (x:ty1 y:ty2. (x,a,y))

type LHsRecProj p arg = XRec p (RecProj p arg) #

type LHsCmdTop p = XRec p (HsCmdTop p) #

Top-level command, introducing a new arrow. This may occur inside a proc (where the stack is empty) or as an argument of a command-forming operator.

Located Haskell Top-level Command

type LHsCmd id = XRec id (HsCmd id) #

Located Haskell Command (for arrow syntax)

type LGRHS id body = XRec id (GRHS id body) #

Located Guarded Right-Hand Side

data HsTupArg id #

Haskell Tuple Argument

Constructors

Present (XPresent id) (LHsExpr id)

The argument

Missing (XMissing id)

The argument is missing, but this is its type

XTupArg !(XXTupArg id)

Note [Trees that Grow] extension point

Instances

Instances details
HiePass p => ToHie (HsTupArg (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsTupArg (GhcPass p) -> HieM [HieAST Type]

data HsStmtContext p #

Haskell Statement Context.

Constructors

ListComp 
MonadComp 
DoExpr (Maybe ModuleName)
ModuleName.
do { ... }
MDoExpr (Maybe ModuleName)
ModuleName.
mdo { ... } ie recursive do-expression
ArrowExpr

do-notation in an arrow-command context

GhciStmtCtxt

A command-line Stmt in GHCi pat <- rhs

PatGuard (HsMatchContext p)

Pattern guard for specified thing

ParStmtCtxt (HsStmtContext p)

A branch of a parallel stmt

TransStmtCtxt (HsStmtContext p)

A branch of a transform stmt

Instances

Instances details
HiePass p => ToHie (HsStmtContext (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsStmtContext (GhcPass p) -> HieM [HieAST Type]

data HsSplicedThing id #

Haskell Spliced Thing

Values that can result from running a splice.

Constructors

HsSplicedExpr (HsExpr id)

Haskell Spliced Expression

HsSplicedTy (HsType id)

Haskell Spliced Type

HsSplicedPat (Pat id)

Haskell Spliced Pattern

type HsRecordBinds p = HsRecFields p (LHsExpr p) #

Haskell Record Bindings

data HsPragE p #

A pragma, written as {-# ... #-}, that may appear within an expression.

data HsMatchContext p #

Haskell Match Context

Context of a pattern match. This is more subtle than it would seem. See Note [Varieties of pattern matches].

Constructors

FunRhs 

Fields

LambdaExpr

Patterns of a lambda

CaseAlt

Patterns and guards on a case alternative

IfAlt

Guards of a multi-way if alternative

ArrowMatchCtxt HsArrowMatchContext

A pattern match inside arrow notation

PatBindRhs

A pattern binding eg [y] <- e = e

PatBindGuards

Guards of pattern bindings, e.g., (Just b) | Just _ <- x = e | otherwise = e'

RecUpd

Record update [used only in GHC.HsToCore.Expr to tell matchWrapper what sort of runtime error message to generate]

StmtCtxt (HsStmtContext p)

Pattern of a do-stmt, list comprehension, pattern guard, etc

ThPatSplice

A Template Haskell pattern splice

ThPatQuote

A Template Haskell pattern quotation [p| (a,b) |]

PatSyn

A pattern synonym declaration

Instances

Instances details
HiePass p => ToHie (HsMatchContext (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsMatchContext (GhcPass p) -> HieM [HieAST Type]

data HsFieldLabel p #

Instances

Instances details
Outputable (HsFieldLabel p) 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

ppr :: HsFieldLabel p -> SDoc #

type family HsDoRn p #

The AST used to hard-refer to GhcPass, which was a layer violation. For now, we paper it over with this new extension point.

Instances

Instances details
type HsDoRn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type HsDoRn (GhcPass _1) = GhcRn

data HsCmdTop p #

Haskell Top-level Command

Constructors

HsCmdTop (XCmdTop p) (LHsCmd p) 
XCmdTop !(XXCmdTop p) 

Instances

Instances details
HiePass p => ToHie (Located (HsCmdTop (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (HsCmdTop (GhcPass p)) -> HieM [HieAST Type]

type Anno (HsCmdTop (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

data HsCmd id #

Haskell Command (e.g. a "statement" in an Arrow proc block)

Instances

Instances details
DisambECP (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (HsCmd GhcPs) :: Type -> Type #

type InfixOp (HsCmd GhcPs) #

type FunArg (HsCmd GhcPs) #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (HsCmd GhcPs)) #

ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (HsCmd GhcPs)) #

mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (HsCmd GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (HsCmd GhcPs))) #

mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) #

mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (HsCmd GhcPs) -> AnnsLet -> PV (LocatedA (HsCmd GhcPs)) #

superInfixOp :: (DisambInfixOp (InfixOp (HsCmd GhcPs)) => PV (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) #

mkHsOpAppPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> LocatedN (InfixOp (HsCmd GhcPs)) -> LocatedA (HsCmd GhcPs) -> PV (LocatedA (HsCmd GhcPs)) #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (HsCmd GhcPs))] -> EpAnnHsCase -> PV (LocatedA (HsCmd GhcPs)) #

mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (HsCmd GhcPs))] -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

superFunArg :: (DisambECP (FunArg (HsCmd GhcPs)) => PV (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) #

mkHsAppPV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> LocatedA (FunArg (HsCmd GhcPs)) -> PV (LocatedA (HsCmd GhcPs)) #

mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsCmd GhcPs)) #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (HsCmd GhcPs) -> Bool -> LocatedA (HsCmd GhcPs) -> AnnsIf -> PV (LocatedA (HsCmd GhcPs)) #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (HsCmd GhcPs))] -> AnnList -> PV (LocatedA (HsCmd GhcPs)) #

mkHsParPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> AnnParen -> PV (LocatedA (HsCmd GhcPs)) #

mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsCmd GhcPs)) #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsCmd GhcPs)) #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsCmd GhcPs)) #

mkHsWildCardPV :: SrcSpan -> PV (Located (HsCmd GhcPs)) #

mkHsTySigPV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsExplicitListPV :: SrcSpan -> [LocatedA (HsCmd GhcPs)] -> AnnList -> PV (LocatedA (HsCmd GhcPs)) #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsCmd GhcPs)) #

mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (HsCmd GhcPs) -> ([Fbind (HsCmd GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsNegAppPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (HsCmd GhcPs)) -> LocatedA (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsLazyPatPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkHsBangPatPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) #

rejectPragmaPV :: LocatedA (HsCmd GhcPs) -> PV () #

HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsCmd (GhcPass p)) -> HieM [HieAST Type]

type Body (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsCmd (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

type family HsBracketRn p #

Instances

Instances details
type HsBracketRn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

data HsBracket p #

Haskell Bracket

Constructors

ExpBr (XExpBr p) (LHsExpr p) 
PatBr (XPatBr p) (LPat p) 
DecBrL (XDecBrL p) [LHsDecl p] 
DecBrG (XDecBrG p) (HsGroup p) 
TypBr (XTypBr p) (LHsType p) 
VarBr (XVarBr p) Bool (LIdP p) 
TExpBr (XTExpBr p) (LHsExpr p) 
XBracket !(XXBracket p) 

Instances

Instances details
ToHie (HsBracket a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsBracket a -> HieM [HieAST Type]

data HsArrowMatchContext #

Haskell arrow match context.

Constructors

ProcExpr

A proc expression

ArrowCaseAlt

A case alternative inside arrow notation

KappaExpr

An arrow kappa abstraction

data HsArrAppType #

Haskell Array Application Type

Instances

Instances details
Data HsArrAppType 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

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

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

toConstr :: HsArrAppType -> Constr #

dataTypeOf :: HsArrAppType -> DataType #

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

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

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

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

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

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

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

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

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

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

type GuardStmt id = Stmt id (LHsExpr id) #

Guard Statement

type GuardLStmt id = LStmt id (LHsExpr id) #

Guard Located Statement

type GhciStmt id = Stmt id (LHsExpr id) #

Ghci Statement

type GhciLStmt id = LStmt id (LHsExpr id) #

Ghci Located Statement

data GRHS p body #

Guarded Right Hand Side.

Constructors

GRHS (XCGRHS p body) [GuardLStmt p] body 
XGRHS !(XXGRHS p body) 

Instances

Instances details
(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

newtype FieldLabelStrings p #

RecordDotSyntax field updates

type FailOperator id = Maybe (SyntaxExpr id) #

The fail operator

This is used for `.. <-` "bind statements" in do notation, including non-monadic "binds" in applicative.

The fail operator is 'Just expr' if it potentially fail monadically. if the pattern match cannot fail, or shouldn't fail monadically (regular incomplete pattern exception), it is Nothing.

See Note [Monad fail : Rebindable syntax, overloaded strings] for the type of expression in the Just case, and why it is so.

See Note [Failing pattern matches in Stmts] for which contexts for 'BindStmt's should use the monadic fail and which shouldn't.

type ExprStmt id = Stmt id (LHsExpr id) #

Expression Statement

type ExprLStmt id = LStmt id (LHsExpr id) #

Expression Located Statement

type CmdSyntaxTable p = [(Name, HsExpr p)] #

Command Syntax Table (for Arrow syntax)

type CmdStmt id = Stmt id (LHsCmd id) #

Command Statement

type CmdLStmt id = LStmt id (LHsCmd id) #

Command Located Statement

data ArithSeqInfo id #

Arithmetic Sequence Information

Constructors

From (LHsExpr id) 
FromThen (LHsExpr id) (LHsExpr id) 
FromTo (LHsExpr id) (LHsExpr id) 
FromThenTo (LHsExpr id) (LHsExpr id) (LHsExpr id) 

Instances

Instances details
ToHie (LHsExpr a) => ToHie (ArithSeqInfo a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: ArithSeqInfo a -> HieM [HieAST Type]

type family ApplicativeArgStmCtxPass idL #

Instances

Instances details
type ApplicativeArgStmCtxPass _1 
Instance details

Defined in GHC.Hs.Expr

data ApplicativeArg idL #

Applicative Argument

Constructors

ApplicativeArgOne 

Fields

  • xarg_app_arg_one :: XApplicativeArgOne idL

    The fail operator, after renaming

    The fail operator is needed if this is a BindStmt where the pattern can fail. E.g.: (Just a) <- stmt The fail operator will be invoked if the pattern match fails. It is also used for guards in MonadComprehensions. The fail operator is Nothing if the pattern match can't fail

  • app_arg_pattern :: LPat idL
     
  • arg_expr :: LHsExpr idL
     
  • is_body_stmt :: Bool

    True = was a BodyStmt, False = was a BindStmt. See Note [Applicative BodyStmt]

ApplicativeArgMany 

Fields

XApplicativeArg !(XXApplicativeArg idL) 

Instances

Instances details
HiePass p => ToHie (RScoped (ApplicativeArg (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (ApplicativeArg (GhcPass p)) -> HieM [HieAST Type]

isMonadStmtContext :: HsStmtContext id -> Bool #

Is this a monadic context?

isInfixMatch :: Match id body -> Bool #

data WarnDecls pass #

Warning pragma Declarations

Constructors

Warnings 

Fields

XWarnDecls !(XXWarnDecls pass) 

Instances

Instances details
ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

type Anno (WarnDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data WarnDecl pass #

Warning pragma Declaration

Constructors

Warning (XWarning pass) [LIdP pass] WarningTxt 
XWarnDecl !(XXWarnDecl pass) 

Instances

Instances details
ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

type Anno (WarnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type TyFamInstEqn pass = FamEqn pass (LHsType pass) #

Type Family Instance Equation

data TyFamInstDecl pass #

Type Family Instance Declaration

Instances

Instances details
ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (TyFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type TyFamDefltDecl = TyFamInstDecl #

Type family default declarations. A convenient synonym for TyFamInstDecl. See Note [Type family instance declarations in HsSyn].

data TyClGroup pass #

Type or Class Group

Instances

Instances details
ToHie (TyClGroup GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TyClGroup GhcRn -> HieM [HieAST Type]

data TyClDecl pass #

A type or class declaration.

Constructors

FamDecl
type/data family T :: *->*

Fields

SynDecl

type declaration

Fields

DataDecl

data declaration

Fields

ClassDecl 

Fields

XTyClDecl !(XXTyClDecl pass) 

Instances

Instances details
ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

type Anno (TyClDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data StandaloneKindSig pass #

Instances

Instances details
ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (StandaloneKindSig GhcRn) 
Instance details

Defined in Compat.HieAst

type Anno (StandaloneKindSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data SpliceDecl p #

Splice Declaration

Instances

Instances details
ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

type Anno (SpliceDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleDecls pass #

Rule Declarations

Constructors

HsRules 

Fields

XRuleDecls !(XXRuleDecls pass) 

Instances

Instances details
ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

type Anno (RuleDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleDecl pass #

Rule Declaration

Constructors

HsRule 

Fields

XRuleDecl !(XXRuleDecl pass) 

Instances

Instances details
ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

type Anno (RuleDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleBndr pass #

Rule Binder

Instances

Instances details
ToHie (RScoped (Located (RuleBndr GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (RuleBndr GhcRn)) -> HieM [HieAST Type]

type Anno (RuleBndr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RoleAnnotDecl pass #

Role Annotation Declaration

Instances

Instances details
ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (RoleAnnotDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data NewOrData #

Constructors

NewType
newtype Blah ...
DataType
data Blah ...

Instances

Instances details
Data NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: NewOrData -> Constr #

dataTypeOf :: NewOrData -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: NewOrData -> SDoc #

Eq NewOrData 
Instance details

Defined in Language.Haskell.Syntax.Decls

type LWarnDecls pass = XRec pass (WarnDecls pass) #

Located Warning Declarations

type LWarnDecl pass = XRec pass (WarnDecl pass) #

Located Warning pragma Declaration

type LTyFamInstEqn pass #

Arguments

 = XRec pass (TyFamInstEqn pass)

May have AnnKeywordId : AnnSemi when in a list

Located Type Family Instance Equation

type LTyFamInstDecl pass = XRec pass (TyFamInstDecl pass) #

Located Type Family Instance Declaration

type LTyFamDefltDecl pass = XRec pass (TyFamDefltDecl pass) #

Located type family default declarations.

type LTyClDecl pass = XRec pass (TyClDecl pass) #

Located Declaration of a Type or Class

type LStandaloneKindSig pass = XRec pass (StandaloneKindSig pass) #

Located Standalone Kind Signature

type LSpliceDecl pass = XRec pass (SpliceDecl pass) #

Located Splice Declaration

type LRuleDecls pass = XRec pass (RuleDecls pass) #

Located Rule Declarations

type LRuleDecl pass = XRec pass (RuleDecl pass) #

Located Rule Declaration

type LRuleBndr pass = XRec pass (RuleBndr pass) #

Located Rule Binder

type LRoleAnnotDecl pass = XRec pass (RoleAnnotDecl pass) #

Located Role Annotation Declaration

type LInstDecl pass = XRec pass (InstDecl pass) #

Located Instance Declaration

type LInjectivityAnn pass = XRec pass (InjectivityAnn pass) #

Located Injectivity Annotation

type LHsFunDep pass = XRec pass (FunDep pass) #

type LHsDerivingClause pass = XRec pass (HsDerivingClause pass) #

type LHsDecl p #

Arguments

 = XRec p (HsDecl p)

When in a list this may have

type LForeignDecl pass = XRec pass (ForeignDecl pass) #

Located Foreign Declaration

type LFamilyResultSig pass = XRec pass (FamilyResultSig pass) #

Located type Family Result Signature

type LFamilyDecl pass = XRec pass (FamilyDecl pass) #

Located type Family Declaration

type LDocDecl pass = XRec pass DocDecl #

Located Documentation comment Declaration

type LDerivDecl pass = XRec pass (DerivDecl pass) #

Located stand-alone 'deriving instance' declaration

type LDerivClauseTys pass = XRec pass (DerivClauseTys pass) #

type LDefaultDecl pass = XRec pass (DefaultDecl pass) #

Located Default Declaration

type LDataFamInstDecl pass = XRec pass (DataFamInstDecl pass) #

Located Data Family Instance Declaration

type LConDecl pass #

Arguments

 = XRec pass (ConDecl pass)

May have AnnKeywordId : AnnSemi when in a GADT constructor list

Located data Constructor Declaration

type LClsInstDecl pass = XRec pass (ClsInstDecl pass) #

Located Class Instance Declaration

type LAnnDecl pass = XRec pass (AnnDecl pass) #

Located Annotation Declaration

data InstDecl pass #

Instance Declaration

Instances

Instances details
ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

type Anno (InstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data InjectivityAnn pass #

If the user supplied an injectivity annotation it is represented using InjectivityAnn. At the moment this is a single injectivity condition - see Note [Injectivity annotation]. `Located name` stores the LHS of injectivity condition. `[Located name]` stores the RHS of injectivity condition. Example:

type family Foo a b c = r | r -> a c where ...

This will be represented as "InjectivityAnn r [a, c]"

Instances

Instances details
ToHie (Located (InjectivityAnn GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (InjectivityAnn (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type HsTyPats pass = [LHsTypeArg pass] #

Haskell Type Patterns

data HsRuleRn #

Constructors

HsRuleRn NameSet NameSet 

Instances

Instances details
Data HsRuleRn 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: HsRuleRn -> Constr #

dataTypeOf :: HsRuleRn -> DataType #

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

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

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

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

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

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

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

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

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

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

data HsGroup p #

Haskell Group

A HsDecl is categorised into a HsGroup before being fed to the renamer.

data HsDerivingClause pass #

A single deriving clause of a data declaration.

Constructors

HsDerivingClause 

Fields

XHsDerivingClause !(XXHsDerivingClause pass) 

Instances

Instances details
ToHie (Located (HsDerivingClause GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (Located [Located (HsDerivingClause GhcRn)]) 
Instance details

Defined in Compat.HieAst

type Anno (HsDerivingClause (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type HsDeriving pass #

Arguments

 = [LHsDerivingClause pass]

The optional deriving clauses of a data declaration. Clauses is plural because one can specify multiple deriving clauses using the -XDerivingStrategies language extension.

The list of LHsDerivingClauses corresponds to exactly what the user requested to derive, in order. If no deriving clauses were specified, the list is empty.

Haskell Deriving clause

data HsDecl p #

A Haskell Declaration

Constructors

TyClD (XTyClD p) (TyClDecl p)

Type or Class Declaration

InstD (XInstD p) (InstDecl p)

Instance declaration

DerivD (XDerivD p) (DerivDecl p)

Deriving declaration

ValD (XValD p) (HsBind p)

Value declaration

SigD (XSigD p) (Sig p)

Signature declaration

KindSigD (XKindSigD p) (StandaloneKindSig p)

Standalone kind signature

DefD (XDefD p) (DefaultDecl p)

'default' declaration

ForD (XForD p) (ForeignDecl p)

Foreign declaration

WarningD (XWarningD p) (WarnDecls p)

Warning declaration

AnnD (XAnnD p) (AnnDecl p)

Annotation declaration

RuleD (XRuleD p) (RuleDecls p)

Rule declaration

SpliceD (XSpliceD p) (SpliceDecl p)

Splice declaration (Includes quasi-quotes)

DocD (XDocD p) DocDecl

Documentation comment declaration

RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p)

Role annotation declaration

XHsDecl !(XXHsDecl p) 

Instances

Instances details
type Anno (HsDecl (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

data HsDataDefn pass #

Haskell Data type Definition

Constructors

HsDataDefn

Declares a data type or newtype, giving its constructors data/newtype T a = constrs data/newtype instance T [a] = constrs

Fields

XHsDataDefn !(XXHsDataDefn pass) 

Instances

Instances details
HasLoc (HsDataDefn GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (HsDataDefn GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsDataDefn GhcRn -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (HsDataDefn GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (HsDataDefn GhcRn)) -> HieM [HieAST Type]

type HsConDeclH98Details pass = HsConDetails Void (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass]) #

The arguments in a Haskell98-style data constructor.

data HsConDeclGADTDetails pass #

The arguments in a GADT constructor. Unlike Haskell98-style constructors, GADT constructors cannot be declared with infix syntax. As a result, we do not use HsConDetails here, as InfixCon would be an unrepresentable state. (There is a notion of infix GADT constructors for the purposes of derived Show instances—see Note [Infix GADT constructors] in GHC.Tc.TyCl—but that is an orthogonal concern.)

Constructors

PrefixConGADT [HsScaled pass (LBangType pass)] 
RecConGADT (XRec pass [LConDeclField pass]) 

Instances

Instances details
ToHie (HsConDeclGADTDetails GhcRn) 
Instance details

Defined in Compat.HieAst

pattern XFunDep :: !(XXFunDep pass) -> FunDep pass #

data ForeignImport #

Instances

Instances details
Data ForeignImport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: ForeignImport -> Constr #

dataTypeOf :: ForeignImport -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignImport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: ForeignImport -> SDoc #

ToHie ForeignImport 
Instance details

Defined in Compat.HieAst

Methods

toHie :: ForeignImport -> HieM [HieAST Type]

data ForeignExport #

Instances

Instances details
Data ForeignExport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: ForeignExport -> Constr #

dataTypeOf :: ForeignExport -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignExport 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: ForeignExport -> SDoc #

ToHie ForeignExport 
Instance details

Defined in Compat.HieAst

Methods

toHie :: ForeignExport -> HieM [HieAST Type]

data ForeignDecl pass #

Foreign Declaration

Instances

Instances details
ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

type Anno (ForeignDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamilyResultSig pass #

type Family Result Signature

Instances

Instances details
ToHie (RScoped (Located (FamilyResultSig GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (Located (FamilyResultSig GhcRn)) -> HieM [HieAST Type]

type Anno (FamilyResultSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamilyInfo pass #

Constructors

DataFamily 
OpenTypeFamily 
ClosedTypeFamily (Maybe [LTyFamInstEqn pass])

Nothing if we're in an hs-boot file and the user said "type family Foo x where .."

Instances

Instances details
Outputable (FamilyInfo pass) 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: FamilyInfo pass -> SDoc #

ToHie (FamilyInfo GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: FamilyInfo GhcRn -> HieM [HieAST Type]

data FamilyDecl pass #

type Family Declaration

Instances

Instances details
ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

type Anno (FamilyDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamEqn pass rhs #

Family Equation

One equation in a type family instance declaration, data family instance declaration, or type family default. See Note [Type family instance declarations in HsSyn] See Note [Family instance declaration binders]

Constructors

FamEqn 

Fields

XFamEqn !(XXFamEqn pass rhs) 

Instances

Instances details
ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (HsDataDefn GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (HsDataDefn GhcRn)) -> HieM [HieAST Type]

(HasLoc a, HiePass p) => HasLoc (FamEqn (GhcPass p) a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: FamEqn (GhcPass p) a -> SrcSpan

(ToHie rhs, HasLoc rhs) => ToHie (FamEqn GhcRn rhs) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: FamEqn GhcRn rhs -> HieM [HieAST Type]

type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

data DocDecl #

Documentation comment Declaration

Instances

Instances details
Data DocDecl 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

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

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

toConstr :: DocDecl -> Constr #

dataTypeOf :: DocDecl -> DataType #

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

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

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

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

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl -> r #

gmapQ :: (forall d. Data d => d -> u) -> DocDecl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DocDecl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl #

Outputable DocDecl 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: DocDecl -> SDoc #

type Anno DocDecl 
Instance details

Defined in GHC.Hs.Decls

data DerivStrategy pass #

Which technique the user explicitly requested when deriving an instance.

Constructors

StockStrategy (XStockStrategy pass)

GHC's "standard" strategy, which is to implement a custom instance for the data type. This only works for certain types that GHC knows about (e.g., Eq, Show, Functor when -XDeriveFunctor is enabled, etc.)

AnyclassStrategy (XAnyClassStrategy pass)
-XDeriveAnyClass
NewtypeStrategy (XNewtypeStrategy pass)
-XGeneralizedNewtypeDeriving
ViaStrategy (XViaStrategy pass)
-XDerivingVia

Instances

Instances details
ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

type Anno (DerivStrategy (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DerivDecl pass #

Stand-alone 'deriving instance' declaration

Constructors

DerivDecl 

Fields

XDerivDecl !(XXDerivDecl pass) 

Instances

Instances details
ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

type Anno (DerivDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DerivClauseTys pass #

The types mentioned in a single deriving clause. This can come in two forms, DctSingle or DctMulti, depending on whether the types are surrounded by enclosing parentheses or not. These parentheses are semantically different than HsParTy. For example, deriving () means "derive zero classes" rather than "derive an instance of the 0-tuple".

DerivClauseTys use LHsSigType because deriving clauses can mention type variables that aren't bound by the datatype, e.g.

data T b = ... deriving (C [a])

should produce a derived instance for C [a] (T b).

Constructors

DctSingle (XDctSingle pass) (LHsSigType pass)

A deriving clause with a single type. Moreover, that type can only be a type constructor without any arguments.

Example: deriving Eq

DctMulti (XDctMulti pass) [LHsSigType pass]

A deriving clause with a comma-separated list of types, surrounded by enclosing parentheses.

Example: deriving (Eq, C a)

XDerivClauseTys !(XXDerivClauseTys pass) 

Instances

Instances details
ToHie (LocatedC (DerivClauseTys GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (DerivClauseTys (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

data DefaultDecl pass #

Default Declaration

Instances

Instances details
ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

type Anno (DefaultDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

newtype DataFamInstDecl pass #

Data Family Instance Declaration

Instances

Instances details
ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

type Anno (DataFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data DataDeclRn #

Constructors

DataDeclRn 

Fields

Instances

Instances details
Data DataDeclRn 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDeclRn -> c DataDeclRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataDeclRn #

toConstr :: DataDeclRn -> Constr #

dataTypeOf :: DataDeclRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataDeclRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataDeclRn) #

gmapT :: (forall b. Data b => b -> b) -> DataDeclRn -> DataDeclRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataDeclRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDeclRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn #

data ConDecl pass #

data T b = forall a. Eq a => MkT a b
  MkT :: forall b a. Eq a => MkT a b

data T b where
     MkT1 :: Int -> T Int

data T = Int MkT Int
       | MkT2

data T a where
     Int MkT Int :: T Int

data Constructor Declaration

Constructors

ConDeclGADT 

Fields

ConDeclH98 

Fields

XConDecl !(XXConDecl pass) 

Instances

Instances details
ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

type Anno (ConDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data ClsInstDecl pass #

Class Instance Declaration

Instances

Instances details
ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

type Anno (ClsInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data CImportSpec #

Instances

Instances details
Data CImportSpec 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CImportSpec -> c CImportSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CImportSpec #

toConstr :: CImportSpec -> Constr #

dataTypeOf :: CImportSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CImportSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CImportSpec) #

gmapT :: (forall b. Data b => b -> b) -> CImportSpec -> CImportSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> CImportSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CImportSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec #

data AnnProvenance pass #

Annotation Provenance

Instances

Instances details
ToHie (AnnProvenance GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: AnnProvenance GhcRn -> HieM [HieAST Type]

data AnnDecl pass #

Annotation Declaration

Instances

Instances details
ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

type Anno (AnnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

isTypeFamilyDecl :: TyClDecl pass -> Bool #

type family declaration

isSynDecl :: TyClDecl pass -> Bool #

type or type instance declaration

isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool #

open type family info

isFamilyDecl :: TyClDecl pass -> Bool #

type/data family declaration

isDataFamilyDecl :: TyClDecl pass -> Bool #

data family declaration

isDataDecl :: TyClDecl pass -> Bool #

True = argument is a data/newtype declaration.

isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool #

closed type family info

isClassDecl :: TyClDecl pass -> Bool #

type class

derivStrategyName :: DerivStrategy a -> SDoc #

A short description of a DerivStrategy'.

countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int) #

data TcSpecPrags #

Type checker Specialisation Pragmas

TcSpecPrags conveys SPECIALISE pragmas from the type checker to the desugarer

Constructors

IsDefaultMethod

Super-specialised: a default method should be macro-expanded at every call site

SpecPrags [LTcSpecPrag] 

Instances

Instances details
Data TcSpecPrags 
Instance details

Defined in Language.Haskell.Syntax.Binds

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrags -> c TcSpecPrags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrags #

toConstr :: TcSpecPrags -> Constr #

dataTypeOf :: TcSpecPrags -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrags) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrags) #

gmapT :: (forall b. Data b => b -> b) -> TcSpecPrags -> TcSpecPrags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r #

gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags #

data TcSpecPrag #

Type checker Specification Pragma

Constructors

SpecPrag Id HsWrapper InlinePragma

The Id to be specialised, a wrapper that specialises the polymorphic function, and inlining spec for the specialised function

Instances

Instances details
Data TcSpecPrag 
Instance details

Defined in Language.Haskell.Syntax.Binds

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrag -> c TcSpecPrag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrag #

toConstr :: TcSpecPrag -> Constr #

dataTypeOf :: TcSpecPrag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrag) #

gmapT :: (forall b. Data b => b -> b) -> TcSpecPrag -> TcSpecPrag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r #

gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag #

data Sig pass #

Signatures and pragmas

Constructors

TypeSig (XTypeSig pass) [LIdP pass] (LHsSigWcType pass)

An ordinary type signature

f :: Num a => a -> a

After renaming, this list of Names contains the named wildcards brought into scope by this signature. For a signature _ -> _a -> Bool, the renamer will leave the unnamed wildcard _ untouched, and the named wildcard _a is then replaced with fresh meta vars in the type. Their names are stored in the type signature that brought them into scope, in this third field to be more specific.

PatSynSig (XPatSynSig pass) [LIdP pass] (LHsSigType pass)

A pattern synonym type signature

pattern Single :: () => (Show a) => a -> [a]
ClassOpSig (XClassOpSig pass) Bool [LIdP pass] (LHsSigType pass)

A signature for a class method False: ordinary class-method signature True: generic-default class method signature e.g. class C a where op :: a -> a -- Ordinary default op :: Eq a => a -> a -- Generic default No wildcards allowed here

IdSig (XIdSig pass) Id

A type signature in generated code, notably the code generated for record selectors. We simply record the desired Id itself, replete with its name, type and IdDetails. Otherwise it's just like a type signature: there should be an accompanying binding

FixSig (XFixSig pass) (FixitySig pass)

An ordinary fixity declaration

    infixl 8 ***
InlineSig (XInlineSig pass) (LIdP pass) InlinePragma

An inline pragma

{#- INLINE f #-}
SpecSig (XSpecSig pass) (LIdP pass) [LHsSigType pass] InlinePragma

A specialisation pragma

{-# SPECIALISE f :: Int -> Int #-}
SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass)

A specialisation pragma for instance declarations only

{-# SPECIALISE instance Eq [Int] #-}

(Class tys); should be a specialisation of the current instance declaration

MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (LIdP pass))

A minimal complete definition pragma

{-# MINIMAL a | (b, c | (d | e)) #-}
SCCFunSig (XSCCFunSig pass) SourceText (LIdP pass) (Maybe (XRec pass StringLiteral))

A "set cost centre" pragma for declarations

{-# SCC funName #-}

or

{-# SCC funName "cost_centre_name" #-}
CompleteMatchSig (XCompleteMatchSig pass) SourceText (XRec pass [LIdP pass]) (Maybe (LIdP pass))

A complete match pragma

{-# COMPLETE C, D [:: T] #-}

Used to inform the pattern match checker about additional complete matchings which, for example, arise from pattern synonym definitions.

XSig !(XXSig pass) 

Instances

Instances details
HiePass p => ToHie (SigContext (LocatedA (Sig (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LocatedA (Sig (GhcPass p))) -> HieM [HieAST Type]

type Anno (Sig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data RecordPatSynField pass #

Record Pattern Synonym Field

Constructors

RecordPatSynField 

Fields

Instances

Instances details
Outputable (RecordPatSynField a) 
Instance details

Defined in Language.Haskell.Syntax.Binds

Methods

ppr :: RecordPatSynField a -> SDoc #

HiePass p => ToHie (PatSynFieldContext (RecordPatSynField (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PatSynFieldContext (RecordPatSynField (GhcPass p)) -> HieM [HieAST Type]

data PatSynBind idL idR #

Pattern Synonym binding

Constructors

PSB 

Fields

XPatSynBind !(XXPatSynBind idL idR) 

Instances

Instances details
HiePass p => ToHie (Located (PatSynBind (GhcPass p) (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (PatSynBind (GhcPass p) (GhcPass p)) -> HieM [HieAST Type]

type LTcSpecPrag = Located TcSpecPrag #

Located Type checker Specification Pragmas

type LSig pass = XRec pass (Sig pass) #

Located Signature

type LIPBind id = XRec id (IPBind id) #

Located Implicit Parameter Binding

May have AnnKeywordId : AnnSemi when in a list

type LHsLocalBindsLR idL idR = XRec idL (HsLocalBindsLR idL idR) #

type LHsLocalBinds id = XRec id (HsLocalBinds id) #

Located Haskell local bindings

type LHsBindsLR idL idR = Bag (LHsBindLR idL idR) #

Located Haskell Bindings with separate Left and Right identifier types

type LHsBinds id = LHsBindsLR id id #

Located Haskell Bindings

type LHsBindLR idL idR = XRec idL (HsBindLR idL idR) #

Located Haskell Binding with separate Left and Right identifier types

type LHsBind id = LHsBindLR id id #

Located Haskell Binding

type LFixitySig pass = XRec pass (FixitySig pass) #

Located Fixity Signature

data IPBind id #

Implicit parameter bindings.

These bindings start off as (Left "x") in the parser and stay that way until after type-checking when they are replaced with (Right d), where "d" is the name of the dictionary holding the evidence for the implicit parameter.

Constructors

IPBind (XCIPBind id) (Either (XRec id HsIPName) (IdP id)) (LHsExpr id) 
XIPBind !(XXIPBind id) 

Instances

Instances details
HiePass p => ToHie (RScoped (LocatedA (IPBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (IPBind (GhcPass p))) -> HieM [HieAST Type]

type Anno (IPBind (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data HsValBindsLR idL idR #

Haskell Value bindings with separate Left and Right identifier types (not implicit parameters) Used for both top level and nested bindings May contain pattern synonym bindings

Constructors

ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR]

Value Bindings In

Before renaming RHS; idR is always RdrName Not dependency analysed Recursive by default

XValBindsLR !(XXValBindsLR idL idR)

Value Bindings Out

After renaming RHS; idR can be Name or Id Dependency analysed, later bindings in the list may depend on earlier ones.

Instances

Instances details
HiePass p => ToHie (RScoped (HsValBindsLR (GhcPass p) (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (HsValBindsLR (GhcPass p) (GhcPass p)) -> HieM [HieAST Type]

type HsValBinds id = HsValBindsLR id id #

Haskell Value Bindings

data HsPatSynDir id #

Haskell Pattern Synonym Direction

Instances

Instances details
HiePass p => ToHie (HsPatSynDir (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsPatSynDir (GhcPass p) -> HieM [HieAST Type]

type HsPatSynDetails pass = HsConDetails Void (LIdP pass) [RecordPatSynField pass] #

Haskell Pattern Synonym Details

data HsLocalBindsLR idL idR #

Haskell Local Bindings with separate Left and Right identifier types

Bindings in a 'let' expression or a 'where' clause

Constructors

HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR)

Haskell Value Bindings

HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR)

Haskell Implicit Parameter Bindings

EmptyLocalBinds (XEmptyLocalBinds idL idR)

Empty Local Bindings

XHsLocalBindsLR !(XXHsLocalBindsLR idL idR) 

Instances

Instances details
HiePass p => ToHie (RScoped (HsLocalBinds (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (HsLocalBinds (GhcPass p)) -> HieM [HieAST Type]

type HsLocalBinds id = HsLocalBindsLR id id #

Haskell Local Bindings

data HsIPBinds id #

Haskell Implicit Parameter Bindings

Constructors

IPBinds (XIPBinds id) [LIPBind id] 
XHsIPBinds !(XXHsIPBinds id) 

data HsBindLR idL idR #

Haskell Binding with separate Left and Right id's

Constructors

FunBind

Function-like Binding

FunBind is used for both functions f x = e and variables f = x -> e and strict variables !x = x + 1

Reason 1: Special case for type inference: see tcMonoBinds.

Reason 2: Instance decls can only have FunBinds, which is convenient. If you change this, you'll need to change e.g. rnMethodBinds

But note that the form f :: a->a = ... parses as a pattern binding, just like (f :: a -> a) = ...

Strict bindings have their strictness recorded in the SrcStrictness of their MatchContext. See Note [FunBind vs PatBind] for details about the relationship between FunBind and PatBind.

AnnKeywordIds

Fields

  • fun_ext :: XFunBind idL idR

    After the renamer (but before the type-checker), this contains the locally-bound free variables of this defn. See Note [Bind free vars]

    After the type-checker, this contains a coercion from the type of the MatchGroup to the type of the Id. Example:

         f :: Int -> forall a. a -> a
         f x y = y
    

    Then the MatchGroup will have type (Int -> a' -> a') (with a free type variable a'). The coercion will take a CoreExpr of this type and convert it to a CoreExpr of type Int -> forall a'. a' -> a' Notice that the coercion captures the free a'.

  • fun_id :: LIdP idL
     
  • fun_matches :: MatchGroup idR (LHsExpr idR)

    The payload

  • fun_tick :: [CoreTickish]

    Ticks to put on the rhs, if any

PatBind

Pattern Binding

The pattern is never a simple variable; That case is done by FunBind. See Note [FunBind vs PatBind] for details about the relationship between FunBind and PatBind.

Fields

VarBind

Variable Binding

Dictionary binding and suchlike. All VarBinds are introduced by the type checker

Fields

AbsBinds

Abstraction Bindings

Fields

PatSynBind

Patterns Synonym Binding

XHsBindsLR !(XXHsBindsLR idL idR) 

Instances

Instances details
HiePass p => HasType (LocatedA (HsBind (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsBind (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LocatedA (HsBind (GhcPass p))) -> HieM [HieAST Type]

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) 
Instance details

Defined in GHC.Hs.Binds

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) = SrcSpanAnnA

type HsBind id = HsBindLR id id #

Haskell Binding

data FixitySig pass #

Fixity Signature

Constructors

FixitySig (XFixitySig pass) [LIdP pass] Fixity 
XFixitySig !(XXFixitySig pass) 

Instances

Instances details
ToHie (LocatedA (FixitySig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FixitySig GhcRn) -> HieM [HieAST Type]

type Anno (FixitySig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data ABExport p #

Abstraction Bindings Export

Constructors

ABE 

Fields

XABExport !(XXABExport p) 

isTypeLSig :: UnXRec p => LSig p -> Bool #

isSpecLSig :: UnXRec p => LSig p -> Bool #

isPragLSig :: UnXRec p => LSig p -> Bool #

hsSigDoc :: Sig name -> SDoc #

type LHsRecUpdField p = XRec p (HsRecUpdField p) #

Located Haskell Record Update Field

type LHsRecField' p id arg = XRec p (HsRecField' id arg) #

Located Haskell Record Field

type LHsRecField p arg = XRec p (HsRecField p arg) #

Located Haskell Record Field

type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) #

Haskell Record Update Field

data HsRecFields p arg #

Haskell Record Fields

HsRecFields is used only for patterns and expressions (not data type declarations)

Constructors

HsRecFields 

Fields

Instances

Instances details
(ToHie arg, HasLoc arg, Data arg, HiePass p) => ToHie (RContext (HsRecFields (GhcPass p) arg)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (HsRecFields (GhcPass p) arg) -> HieM [HieAST Type]

(Outputable arg, Outputable (XRec p (HsRecField p arg))) => Outputable (HsRecFields p arg) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsRecFields p arg -> SDoc #

data HsRecField' id arg #

Haskell Record Field

For details on above see note [exact print annotations] in GHC.Parser.Annotation

Constructors

HsRecField 

Fields

Instances

Instances details
Foldable (HsRecField' id) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

fold :: Monoid m => HsRecField' id m -> m #

foldMap :: Monoid m => (a -> m) -> HsRecField' id a -> m #

foldMap' :: Monoid m => (a -> m) -> HsRecField' id a -> m #

foldr :: (a -> b -> b) -> b -> HsRecField' id a -> b #

foldr' :: (a -> b -> b) -> b -> HsRecField' id a -> b #

foldl :: (b -> a -> b) -> b -> HsRecField' id a -> b #

foldl' :: (b -> a -> b) -> b -> HsRecField' id a -> b #

foldr1 :: (a -> a -> a) -> HsRecField' id a -> a #

foldl1 :: (a -> a -> a) -> HsRecField' id a -> a #

toList :: HsRecField' id a -> [a] #

null :: HsRecField' id a -> Bool #

length :: HsRecField' id a -> Int #

elem :: Eq a => a -> HsRecField' id a -> Bool #

maximum :: Ord a => HsRecField' id a -> a #

minimum :: Ord a => HsRecField' id a -> a #

sum :: Num a => HsRecField' id a -> a #

product :: Num a => HsRecField' id a -> a #

Traversable (HsRecField' id) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

traverse :: Applicative f => (a -> f b) -> HsRecField' id a -> f (HsRecField' id b) #

sequenceA :: Applicative f => HsRecField' id (f a) -> f (HsRecField' id a) #

mapM :: Monad m => (a -> m b) -> HsRecField' id a -> m (HsRecField' id b) #

sequence :: Monad m => HsRecField' id (m a) -> m (HsRecField' id a) #

Functor (HsRecField' id) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

fmap :: (a -> b) -> HsRecField' id a -> HsRecField' id b #

(<$) :: a -> HsRecField' id b -> HsRecField' id a #

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data arg, Data label) => ToHie (RContext (LocatedA (HsRecField' label arg))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LocatedA (HsRecField' label arg)) -> HieM [HieAST Type]

(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsRecField' p arg) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsRecField' p arg -> SDoc #

type Anno (HsRecField (GhcPass p) arg) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' p arg) 
Instance details

Defined in GHC.Hs.Pat

type HsRecField p arg = HsRecField' (FieldOcc p) arg #

Haskell Record Field

type HsConPatDetails p = HsConDetails (HsPatSigType (NoGhcTc p)) (LPat p) (HsRecFields p (LPat p)) #

Haskell Constructor Pattern Details

type family ConLikeP x #

Instances

Instances details
type ConLikeP GhcPs 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcRn 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcTc 
Instance details

Defined in GHC.Hs.Pat

hsRecFieldsArgs :: UnXRec p => HsRecFields p arg -> [arg] #

type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) #

Located Haskell Wildcard Type

type LHsTypeArg p = HsArg (LHsType p) (LHsKind p) #

type LHsType pass #

Arguments

 = XRec pass (HsType pass)

May have AnnKeywordId : AnnComma when in a list

Located Haskell Type

type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass) #

Located Haskell Type Variable Binder

type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) #

Located Haskell Signature Wildcard Type

type LHsSigType pass = XRec pass (HsSigType pass) #

Located Haskell Signature Type

data LHsQTyVars pass #

Located Haskell Quantified Type Variables

Constructors

HsQTvs 

Fields

XLHsQTyVars !(XXLHsQTyVars pass) 

Instances

Instances details
ToHie (TScoped (LHsQTyVars GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]

type LHsKind pass #

Arguments

 = XRec pass (HsKind pass)

AnnKeywordId : AnnDcolon

Located Haskell Kind

type LHsContext pass #

Arguments

 = XRec pass (HsContext pass)

AnnKeywordId : AnnUnit For details on above see note [exact print annotations] in GHC.Parser.Annotation

Located Haskell Context

type LFieldOcc pass = XRec pass (FieldOcc pass) #

Located Field Occurrence

type LConDeclField pass #

Arguments

 = XRec pass (ConDeclField pass)

May have AnnKeywordId : AnnComma when in a list

Located Constructor Declaration Field

type LBangType pass = XRec pass (BangType pass) #

Located Bang Type

data HsWildCardBndrs pass thing #

Haskell Wildcard Binders

Constructors

HsWC 

Fields

XHsWildCardBndrs !(XXHsWildCardBndrs pass thing) 

Instances

Instances details
ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

data HsType pass #

Haskell Type

Constructors

HsForAllTy
HsQualTy 

Fields

HsTyVar (XTyVar pass) PromotionFlag (LIdP pass)
HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
HsAppKindTy (XAppKindTy pass) (LHsType pass) (LHsKind pass) 
HsFunTy (XFunTy pass) (HsArrow pass) (LHsType pass) (LHsType pass)
HsListTy (XListTy pass) (LHsType pass)
HsTupleTy (XTupleTy pass) HsTupleSort [LHsType pass]
HsSumTy (XSumTy pass) [LHsType pass]
HsOpTy (XOpTy pass) (LHsType pass) (LIdP pass) (LHsType pass)
HsParTy (XParTy pass) (LHsType pass)
HsIParamTy (XIParamTy pass) (XRec pass HsIPName) (LHsType pass)
(?x :: ty)
HsStarTy (XStarTy pass) Bool
HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
(ty :: kind)
HsSpliceTy (XSpliceTy pass) (HsSplice pass)
HsDocTy (XDocTy pass) (LHsType pass) LHsDocString
HsBangTy (XBangTy pass) HsSrcBang (LHsType pass)
HsRecTy (XRecTy pass) [LConDeclField pass]
HsExplicitListTy (XExplicitListTy pass) PromotionFlag [LHsType pass]
HsExplicitTupleTy (XExplicitTupleTy pass) [LHsType pass]
HsTyLit (XTyLit pass) HsTyLit
HsWildCardTy (XWildCardTy pass)
XHsType !(XXType pass) 

Instances

Instances details
DisambTD (HsType GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

ToHie (LocatedA (HsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsType GhcRn) -> HieM [HieAST Type]

ToHie (LocatedC [LocatedA (HsType GhcRn)]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedC [LocatedA (HsType GhcRn)] -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

type Anno (BangType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsKind (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (HsType (GhcPass p))] 
Instance details

Defined in GHC.Hs.Type

type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

data HsTyVarBndr flag pass #

Haskell Type Variable Binder The flag annotates the binder. It is Specificity in places where explicit specificity is allowed (e.g. x :: forall {a} b. ...) or () in other places.

Constructors

UserTyVar (XUserTyVar pass) flag (LIdP pass) 
KindedTyVar (XKindedTyVar pass) flag (LIdP pass) (LHsKind pass)
XTyVarBndr !(XXTyVarBndr pass) 

Instances

Instances details
Data flag => ToHie (TVScoped (LocatedA (HsTyVarBndr flag GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LocatedA (HsTyVarBndr flag GhcRn)) -> HieM [HieAST Type]

type Anno (HsTyVarBndr _flag (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) = SrcSpanAnnA
type Anno (HsTyVarBndr _flag GhcPs) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcRn) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcTc) 
Instance details

Defined in GHC.Hs.Type

data HsTyLit #

Haskell Type Literal

Instances

Instances details
Data HsTyLit 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit -> c HsTyLit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTyLit #

toConstr :: HsTyLit -> Constr #

dataTypeOf :: HsTyLit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTyLit) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTyLit) #

gmapT :: (forall b. Data b => b -> b) -> HsTyLit -> HsTyLit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTyLit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit #

Outputable HsTyLit 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsTyLit -> SDoc #

data HsTupleSort #

Haskell Tuple Sort

Instances

Instances details
Data HsTupleSort 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTupleSort #

toConstr :: HsTupleSort -> Constr #

dataTypeOf :: HsTupleSort -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTupleSort) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTupleSort) #

gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTupleSort -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort #

data HsSigType pass #

A type signature that obeys the forall-or-nothing rule. In other words, an LHsType that uses an HsOuterSigTyVarBndrs to represent its outermost type variable quantification. See Note [Representing type signatures].

Constructors

HsSig 

Fields

XHsSigType !(XXHsSigType pass) 

Instances

Instances details
ToHie (TScoped (LocatedA (HsSigType GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LocatedA (HsSigType GhcRn)) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

type Anno (HsSigType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

data HsScaled pass a #

This is used in the syntax. In constructor declaration. It must keep the arrow representation.

Constructors

HsScaled (HsArrow pass) a 

Instances

Instances details
Outputable a => Outputable (HsScaled pass a) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsScaled pass a -> SDoc #

ToHie a => ToHie (HsScaled GhcRn a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsScaled GhcRn a -> HieM [HieAST Type]

data HsPatSigType pass #

Types that can appear in pattern signatures, as well as the signatures for term-level binders in RULES. See Note [Pattern signature binders and scoping].

This is very similar to HsSigWcType, but with slightly different semantics: see Note [HsType binders]. See also Note [The wildcard story for types].

Constructors

HsPS 

Fields

XHsPatSigType !(XXHsPatSigType pass) 

Instances

Instances details
ToHie (TScoped (HsPatSigType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]

data HsPSRn #

The extension field for HsPatSigType, which is only used in the renamer onwards. See Note [Pattern signature binders and scoping].

Constructors

HsPSRn 

Fields

Instances

Instances details
Data HsPSRn 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPSRn -> c HsPSRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsPSRn #

toConstr :: HsPSRn -> Constr #

dataTypeOf :: HsPSRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsPSRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsPSRn) #

gmapT :: (forall b. Data b => b -> b) -> HsPSRn -> HsPSRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPSRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPSRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsPSRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPSRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPSRn -> m HsPSRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPSRn -> m HsPSRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPSRn -> m HsPSRn #

data HsOuterTyVarBndrs flag pass #

The outermost type variables in a type that obeys the forall-or-nothing rule. See Note [forall-or-nothing rule].

Constructors

HsOuterImplicit

Implicit forall, e.g., f :: a -> b -> b

HsOuterExplicit

Explicit forall, e.g., f :: forall a b. a -> b -> b

Fields

XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass) 

Instances

Instances details
Data flag => ToHie (TVScoped (HsOuterTyVarBndrs flag GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (HsOuterTyVarBndrs flag GhcRn) -> HieM [HieAST Type]

type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) 
Instance details

Defined in GHC.Hs.Type

type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity #

Used for signatures, e.g.,

f :: forall a {b}. blah

We use Specificity for the HsOuterTyVarBndrs flag to allow distinguishing between specified and inferred type variables.

type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs () #

Used for type-family instance equations, e.g.,

type instance forall a. F [a] = Tree a

The notion of specificity is irrelevant in type family equations, so we use () for the HsOuterTyVarBndrs flag.

type HsKind pass = HsType pass #

Haskell Kind

newtype HsIPName #

These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.

Constructors

HsIPName FastString 

Instances

Instances details
Data HsIPName 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPName -> c HsIPName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsIPName #

toConstr :: HsIPName -> Constr #

dataTypeOf :: HsIPName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsIPName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName) #

gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsIPName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName #

Outputable HsIPName 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsIPName -> SDoc #

OutputableBndr HsIPName 
Instance details

Defined in Language.Haskell.Syntax.Type

Eq HsIPName 
Instance details

Defined in Language.Haskell.Syntax.Type

ToHie (Located HsIPName) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located HsIPName -> HieM [HieAST Type]

type Anno HsIPName 
Instance details

Defined in GHC.Hs.Type

data HsForAllTelescope pass #

The type variable binders in an HsForAllTy. See also Note [Variable Specificity and Forall Visibility] in GHC.Tc.Gen.HsType.

Constructors

HsForAllVis

A visible forall (e.g., forall a -> {...}). These do not have any notion of specificity, so we use () as a placeholder value.

Fields

HsForAllInvis

An invisible forall (e.g., forall a {b} c. {...}), where each binder has a Specificity.

XHsForAllTelescope !(XXHsForAllTelescope pass) 

type HsCoreTy = Type #

type HsContext pass = [LHsType pass] #

Haskell Context

data HsConDetails tyarg arg rec #

Describes the arguments to a data constructor. This is a common representation for several constructor-related concepts, including:

  • The arguments in a Haskell98-style constructor declaration (see HsConDeclH98Details in GHC.Hs.Decls).
  • The arguments in constructor patterns in case/function definitions (see HsConPatDetails in GHC.Hs.Pat).
  • The left-hand side arguments in a pattern synonym binding (see HsPatSynDetails in GHC.Hs.Binds).

One notable exception is the arguments in a GADT constructor, which uses a separate data type entirely (see HsConDeclGADTDetails in GHC.Hs.Decls). This is because GADT constructors cannot be declared with infix syntax, unlike the concepts above (#18844).

Constructors

PrefixCon [tyarg] [arg] 
RecCon rec 
InfixCon arg arg 

Instances

Instances details
(Data tyarg, Data arg, Data rec) => Data (HsConDetails tyarg arg rec) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails tyarg arg rec -> c (HsConDetails tyarg arg rec) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec) #

toConstr :: HsConDetails tyarg arg rec -> Constr #

dataTypeOf :: HsConDetails tyarg arg rec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails tyarg arg rec)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails tyarg arg rec)) #

gmapT :: (forall b. Data b => b -> b) -> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

(Outputable tyarg, Outputable arg, Outputable rec) => Outputable (HsConDetails tyarg arg rec) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsConDetails tyarg arg rec -> SDoc #

(ToHie tyarg, ToHie arg, ToHie rec) => ToHie (HsConDetails tyarg arg rec) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsConDetails tyarg arg rec -> HieM [HieAST Type]

data HsArrow pass #

Denotes the type of arrows in the surface language

Constructors

HsUnrestrictedArrow IsUnicodeSyntax

a -> b or a → b

HsLinearArrow IsUnicodeSyntax (Maybe AddEpAnn)

a %1 -> b or a %1 → b, or a ⊸ b

HsExplicitMult IsUnicodeSyntax (Maybe AddEpAnn) (LHsType pass)

a %m -> b or a %m → b (very much including `a %Many -> b`! This is how the programmer wrote it). It is stored as an HsType so as to preserve the syntax as written in the program.

data HsArg tm ty #

Constructors

HsValArg tm 
HsTypeArg SrcSpan ty 
HsArgPar SrcSpan 

Instances

Instances details
(Outputable tm, Outputable ty) => Outputable (HsArg tm ty) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsArg tm ty -> SDoc #

(HasLoc tm, HasLoc ty) => HasLoc (HsArg tm ty) 
Instance details

Defined in Compat.HieAst

Methods

loc :: HsArg tm ty -> SrcSpan

(ToHie tm, ToHie ty) => ToHie (HsArg tm ty) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsArg tm ty -> HieM [HieAST Type]

data FieldOcc pass #

Field Occurrence

Represents an *occurrence* of an unambiguous field. This may or may not be a binding occurrence (e.g. this type is used in ConDeclField and RecordPatSynField which bind their fields, but also in HsRecField for record construction and patterns, which do not).

We store both the RdrName the user originally wrote, and after the renamer, the selector function.

Constructors

FieldOcc 

Fields

XFieldOcc !(XXFieldOcc pass) 

Instances

Instances details
Outputable (FieldOcc pass) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: FieldOcc pass -> SDoc #

OutputableBndr (FieldOcc pass) 
Instance details

Defined in Language.Haskell.Syntax.Type

(Eq (XCFieldOcc pass), Eq (XXFieldOcc pass)) => Eq (FieldOcc pass) 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

(==) :: FieldOcc pass -> FieldOcc pass -> Bool #

(/=) :: FieldOcc pass -> FieldOcc pass -> Bool #

HiePass p => ToHie (Context (FieldOcc (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (FieldOcc (GhcPass p)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (FieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (FieldOcc GhcTc)) -> HieM [HieAST Type]

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) 
Instance details

Defined in Language.Haskell.Syntax.Type

type Anno (FieldOcc (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsRecField (GhcPass p) arg) 
Instance details

Defined in GHC.Hs.Pat

data ConDeclField pass #

Constructor Declaration Field

Constructors

ConDeclField 

Fields

XConDeclField !(XXConDeclField pass) 

Instances

Instances details
ToHie (LocatedA (ConDeclField GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDeclField GhcRn) -> HieM [HieAST Type]

ToHie (LocatedL [LocatedA (ConDeclField GhcRn)]) 
Instance details

Defined in Compat.HieAst

type Anno (ConDeclField (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (ConDeclField (GhcPass _1))] 
Instance details

Defined in GHC.Hs.Decls

type BangType pass = HsType pass #

Bang Type

In the parser, strictness and packedness annotations bind more tightly than docstrings. This means that when consuming a BangType (and looking for HsBangTy) we must be ready to peer behind a potential layer of HsDocTy. See #15206 for motivation and getBangType for an example.

data AmbiguousFieldOcc pass #

Ambiguous Field Occurrence

Represents an *occurrence* of a field that is potentially ambiguous after the renamer, with the ambiguity resolved by the typechecker. We always store the RdrName that the user originally wrote, and store the selector function after the renamer (for unambiguous occurrences) or the typechecker (for ambiguous occurrences).

See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and Note [Disambiguating record fields] in GHC.Tc.Gen.Head. See Note [Located RdrNames] in GHC.Hs.Expr

Instances

Instances details
ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]

type Anno (AmbiguousFieldOcc GhcTc) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) 
Instance details

Defined in GHC.Hs.Pat

numVisibleArgs :: [HsArg tm ty] -> Arity #

noTypeArgs :: [Void] #

An empty list that can be used to indicate that there are no type arguments allowed in cases where HsConDetails is applied to Void.

isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool #

Does this HsTyVarBndr come with an explicit kind annotation?

hsUnrestricted :: a -> HsScaled pass a #

When creating syntax we use the shorthands. It's better for printing, also, the shorthands work trivially at each pass.

hsScaledThing :: HsScaled pass a -> a #

hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr () pass] #

hsMult :: HsScaled pass a -> HsArrow pass #

hsLinear :: a -> HsScaled pass a #

When creating syntax we use the shorthands. It's better for printing, also, the shorthands work trivially at each pass.

data Pat p #

Constructors

WildPat (XWildPat p)

Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type

VarPat (XVarPat p) (LIdP p)

Variable Pattern

LazyPat (XLazyPat p) (LPat p)

Lazy Pattern ^ - AnnKeywordId : AnnTilde

AsPat (XAsPat p) (LIdP p) (LPat p)

As pattern ^ - AnnKeywordId : AnnAt

ParPat (XParPat p) (LPat p)

Parenthesised pattern See Note [Parens in HsSyn] in GHC.Hs.Expr ^ - AnnKeywordId : AnnOpen '(', AnnClose ')'

BangPat (XBangPat p) (LPat p)

Bang pattern ^ - AnnKeywordId : AnnBang

ListPat (XListPat p) [LPat p]

Syntactic List

TuplePat (XTuplePat p) [LPat p] Boxity

Tuple sub-patterns

SumPat (XSumPat p) (LPat p) ConTag Arity

Anonymous sum pattern

ConPat

Constructor Pattern

ViewPat

Fields

SplicePat

Fields

LitPat (XLitPat p) (HsLit p)

Literal Pattern Used for *non-overloaded* literal patterns: Int#, Char#, Int, Char, String, etc.

NPat (XNPat p) (XRec p (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)

Natural Pattern

NPlusKPat (XNPlusKPat p) (LIdP p) (XRec p (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)

n+k pattern

SigPat

Fields

XPat !(XXPat p)

Trees that Grow extension point for new constructors

Instances

Instances details
HiePass p => HasType (LocatedA (Pat (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (Pat (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (LocatedA (Pat (GhcPass p))) -> HieM [HieAST Type]

type Anno (Pat (GhcPass p)) 
Instance details

Defined in GHC.Hs.Pat

type LPat p = XRec p (Pat p) #

data OverLitVal #

Overloaded Literal Value

Constructors

HsIntegral !IntegralLit

Integer-looking literals;

HsFractional !FractionalLit

Frac-looking literals

HsIsString !SourceText !FastString

String-looking literals

Instances

Instances details
Data OverLitVal 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitVal -> c OverLitVal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitVal #

toConstr :: OverLitVal -> Constr #

dataTypeOf :: OverLitVal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitVal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitVal) #

gmapT :: (forall b. Data b => b -> b) -> OverLitVal -> OverLitVal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r #

gmapQ :: (forall d. Data d => d -> u) -> OverLitVal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitVal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal #

Outputable OverLitVal 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

ppr :: OverLitVal -> SDoc #

Eq OverLitVal 
Instance details

Defined in Language.Haskell.Syntax.Lit

Ord OverLitVal 
Instance details

Defined in Language.Haskell.Syntax.Lit

data HsOverLit p #

Haskell Overloaded Literal

Constructors

OverLit 
XOverLit !(XXOverLit p) 

Instances

Instances details
Eq (XXOverLit p) => Eq (HsOverLit p) 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

(==) :: HsOverLit p -> HsOverLit p -> Bool #

(/=) :: HsOverLit p -> HsOverLit p -> Bool #

Ord (XXOverLit p) => Ord (HsOverLit p) 
Instance details

Defined in Language.Haskell.Syntax.Lit

type Anno (HsOverLit (GhcPass p)) 
Instance details

Defined in GHC.Hs.Pat

data HsLit x #

Haskell Literal

Constructors

HsChar (XHsChar x) Char

Character

HsCharPrim (XHsCharPrim x) Char

Unboxed character

HsString (XHsString x) FastString

String

HsStringPrim (XHsStringPrim x) !ByteString

Packed bytes

HsInt (XHsInt x) IntegralLit

Genuinely an Int; arises from GHC.Tc.Deriv.Generate, and from TRANSLATION

HsIntPrim (XHsIntPrim x) Integer

literal Int#

HsWordPrim (XHsWordPrim x) Integer

literal Word#

HsInt64Prim (XHsInt64Prim x) Integer

literal Int64#

HsWord64Prim (XHsWord64Prim x) Integer

literal Word64#

HsInteger (XHsInteger x) Integer Type

Genuinely an integer; arises only from TRANSLATION (overloaded literals are done with HsOverLit)

HsRat (XHsRat x) FractionalLit Type

Genuinely a rational; arises only from TRANSLATION (overloaded literals are done with HsOverLit)

HsFloatPrim (XHsFloatPrim x) FractionalLit

Unboxed Float

HsDoublePrim (XHsDoublePrim x) FractionalLit

Unboxed Double

XLit !(XXLit x) 

Instances

Instances details
Eq (HsLit x) 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

(==) :: HsLit x -> HsLit x -> Bool #

(/=) :: HsLit x -> HsLit x -> Bool #

hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool #

hsOverLitNeedsParens p ol returns True if an overloaded literal ol needs to be parenthesized under precedence p.

hsLitNeedsParens :: PprPrec -> HsLit x -> Bool #

hsLitNeedsParens p l returns True if a literal l needs to be parenthesized under precedence p.

type family SyntaxExpr p #

Syntax Expression

SyntaxExpr is represents the function used in interpreting rebindable syntax. In the parser, we have no information to supply; in the renamer, we have the name of the function (but see Note [Monad fail : Rebindable syntax, overloaded strings] for a wrinkle) and in the type-checker we have a more elaborate structure SyntaxExprTc.

In some contexts, rebindable syntax is not implemented, and so we have constructors to represent that possibility in both the renamer and typechecker instantiations.

E.g. (>>=) is filled in before the renamer by the appropriate Name for (>>=), and then instantiated by the type checker with its type args etc

Instances

Instances details
type SyntaxExpr (GhcPass p) 
Instance details

Defined in GHC.Hs.Expr

data MatchGroup p body #

Constructors

MG 

Fields

XMatchGroup !(XXMatchGroup p body) 

Instances

Instances details
(HiePass p, AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

type LHsExpr p #

Arguments

 = XRec p (HsExpr p)

May have AnnKeywordId : AnnComma when in a list

Located Haskell Expression

data HsSplice id #

Haskell Splice

Instances

Instances details
HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsSplice (GhcPass p)) -> HieM [HieAST Type]

type Anno (HsSplice (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

data HsExpr p #

A Haskell expression.

Constructors

HsVar (XVar p) (LIdP p)

Variable See Note [Located RdrNames]

HsUnboundVar (XUnboundVar p) OccName

Unbound variable; also used for "holes" (_ or _x). Turned from HsVar to HsUnboundVar by the renamer, when it finds an out-of-scope variable or hole. The (XUnboundVar p) field becomes an HoleExprRef after typechecking; this is where the erroring expression will be written after solving. See Note [Holes] in GHC.Tc.Types.Constraint.

HsConLikeOut (XConLikeOut p) ConLike

After typechecker only; must be different HsVar for pretty printing

HsRecFld (XRecFld p) (AmbiguousFieldOcc p)

Variable pointing to record selector The parser produces HsVars The renamer renames record-field selectors to HsRecFld The typechecker preserves HsRecFld

HsOverLabel (XOverLabel p) FastString

Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels)

HsIPVar (XIPVar p) HsIPName

Implicit parameter (not in use after typechecking)

HsOverLit (XOverLitE p) (HsOverLit p)

Overloaded literals

HsLit (XLitE p) (HsLit p)

Simple (non-overloaded) literals

HsLam (XLam p) (MatchGroup p (LHsExpr p))

Lambda abstraction. Currently always a single match

HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p))

Lambda-case

HsApp (XApp p) (LHsExpr p) (LHsExpr p)

Application

HsAppType (XAppTypeE p) (LHsExpr p) (LHsWcType (NoGhcTc p))

Visible type application

Explicit type argument; e.g f @Int x y NB: Has wildcards, but no implicit quantification

OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p)

Operator applications: NB Bracketed ops such as (+) come out as Vars.

NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p)

Negation operator. Contains the negated expression and the name of negate

HsPar

Fields

  • (XPar p)
     
  • (LHsExpr p)

    Parenthesised expr; see Note [Parens in HsSyn]

SectionL (XSectionL p) (LHsExpr p) (LHsExpr p) 
SectionR (XSectionR p) (LHsExpr p) (LHsExpr p) 
ExplicitTuple (XExplicitTuple p) [HsTupArg p] Boxity

Used for explicit tuples and sections thereof

ExplicitSum (XExplicitSum p) ConTag Arity (LHsExpr p)

Used for unboxed sum types

There will be multiple AnnVbar, (1 - alternative) before the expression, (arity - alternative) after it

HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p))
HsIf (XIf p) (LHsExpr p) (LHsExpr p) (LHsExpr p)
HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)]

Multi-way if

HsLet (XLet p) (HsLocalBinds p) (LHsExpr p)

let(rec)

HsDo (XDo p) (HsStmtContext (HsDoRn p)) (XRec p [ExprLStmt p])
ExplicitList (XExplicitList p) [LHsExpr p]

Syntactic list: [a,b,c,...]

RecordCon

Record construction

RecordUpd

Record update

HsGetField

Record field selection e.g z.x.

This case only arises when the OverloadedRecordDot langauge extension is enabled.

HsProjection

Record field selector. e.g. (.x) or (.x.y)

This case only arises when the OverloadedRecordDot langauge extensions is enabled.

ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))

Expression with an explicit type signature. e :: type

ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p)

Arithmetic sequence

HsBracket (XBracket p) (HsBracket p)
HsRnBracketOut (XRnBracketOut p) (HsBracket (HsBracketRn p)) [PendingRnSplice' p] 
HsTcBracketOut (XTcBracketOut p) (Maybe QuoteWrapper) (HsBracket (HsBracketRn p)) [PendingTcSplice' p] 
HsSpliceE (XSpliceE p) (HsSplice p)
HsProc (XProc p) (LPat p) (LHsCmdTop p)

proc notation for Arrows

HsStatic (XStatic p) (LHsExpr p)
HsTick (XTick p) CoreTickish (LHsExpr p) 
HsBinTick (XBinTick p) Int Int (LHsExpr p) 
HsPragE (XPragE p) (HsPragE p) (LHsExpr p) 
XExpr !(XXExpr p) 

Instances

Instances details
DisambECP (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (HsExpr GhcPs) :: Type -> Type #

type InfixOp (HsExpr GhcPs) #

type FunArg (HsExpr GhcPs) #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (HsExpr GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (HsExpr GhcPs))) #

mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (HsExpr GhcPs) -> AnnsLet -> PV (LocatedA (HsExpr GhcPs)) #

superInfixOp :: (DisambInfixOp (InfixOp (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsOpAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> LocatedN (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> EpAnnHsCase -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

superFunArg :: (DisambECP (FunArg (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAppPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LocatedA (FunArg (HsExpr GhcPs)) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (HsExpr GhcPs) -> Bool -> LocatedA (HsExpr GhcPs) -> AnnsIf -> PV (LocatedA (HsExpr GhcPs)) #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (HsExpr GhcPs))] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) #

mkHsParPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> AnnParen -> PV (LocatedA (HsExpr GhcPs)) #

mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsWildCardPV :: SrcSpan -> PV (Located (HsExpr GhcPs)) #

mkHsTySigPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsExplicitListPV :: SrcSpan -> [LocatedA (HsExpr GhcPs)] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (HsExpr GhcPs) -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsNegAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLazyPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsBangPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

rejectPragmaPV :: LocatedA (HsExpr GhcPs) -> PV () #

DisambInfixOp (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

HiePass p => HasType (LocatedA (HsExpr (GhcPass p)))

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

type Body (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsExpr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

data GRHSs p body #

Guarded Right-Hand Sides

GRHSs are used both for pattern bindings and for Matches

Constructors

GRHSs 

Fields

XGRHSs !(XXGRHSs p body) 

Instances

Instances details
(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

type family XXWarnDecls x #

Instances

Instances details
type XXWarnDecls (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecl x #

Instances

Instances details
type XXWarnDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXValBindsLR x x' #

Instances

Instances details
type XXValBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XXType x #

Instances

Instances details
type XXType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXType (GhcPass _1) = HsCoreTy

type family XXTyVarBndr x #

Instances

Instances details
type XXTyVarBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXTyFamInstDecl x #

Instances

Instances details
type XXTyFamInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClGroup x #

Instances

Instances details
type XXTyClGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClDecl x #

Instances

Instances details
type XXTyClDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXTupArg x #

Instances

Instances details
type XXTupArg (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXStmtLR x x' b #

Instances

Instances details
type XXStmtLR (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon

type family XXStandaloneKindSig x #

Instances

Instances details
type XXStandaloneKindSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Decls

type family XXSpliceDecl x #

Instances

Instances details
type XXSpliceDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXSplice x #

Instances

Instances details
type XXSplice GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XXSig x #

Instances

Instances details
type XXSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XXRuleDecls x #

Instances

Instances details
type XXRuleDecls (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecl x #

Instances

Instances details
type XXRuleDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleBndr x #

Instances

Instances details
type XXRuleBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXRoleAnnotDecl x #

Instances

Instances details
type XXRoleAnnotDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXPragE x #

Instances

Instances details
type XXPragE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXPatSynBind x x' #

Instances

Instances details
type XXPatSynBind (GhcPass idL) (GhcPass idR) 
Instance details

Defined in GHC.Hs.Binds

type family XXPat x #

Instances

Instances details
type XXPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XXParStmtBlock x x' #

Instances

Instances details
type XXParStmtBlock (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Expr

type family XXOverLit x #

Instances

Instances details
type XXOverLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XXMatchGroup x b #

Instances

Instances details
type XXMatchGroup (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type family XXMatch x b #

Instances

Instances details
type XXMatch (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _1) b = NoExtCon

type family XXLit x #

Instances

Instances details
type XXLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XXLit (GhcPass _1) = NoExtCon

type family XXLHsQTyVars x #

Instances

Instances details
type XXLHsQTyVars (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXInstDecl x #

Instances

Instances details
type XXInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXInjectivityAnn x #

Instances

Instances details
type XXInjectivityAnn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXImportDecl x #

Instances

Instances details
type XXImportDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XXIPBind x #

Instances

Instances details
type XXIPBind (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XXIE x #

Instances

Instances details
type XXIE (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _1) = NoExtCon

type family XXHsWildCardBndrs x b #

Instances

Instances details
type XXHsWildCardBndrs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Type

type family XXHsSigType x #

Instances

Instances details
type XXHsSigType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXHsPatSigType x #

Instances

Instances details
type XXHsPatSigType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXHsOuterTyVarBndrs x #

Instances

Instances details
type XXHsOuterTyVarBndrs (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXHsLocalBindsLR x x' #

Instances

Instances details
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XXHsIPBinds x #

Instances

Instances details
type XXHsIPBinds (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XXHsGroup x #

Instances

Instances details
type XXHsGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXHsForAllTelescope x #

Instances

Instances details
type XXHsForAllTelescope (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXHsFieldLabel x #

Instances

Instances details
type XXHsFieldLabel (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXHsDerivingClause x #

Instances

Instances details
type XXHsDerivingClause (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDecl x #

Instances

Instances details
type XXHsDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDataDefn x #

Instances

Instances details
type XXHsDataDefn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXHsBindsLR x x' #

Instances

Instances details
type XXHsBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XXGRHSs x b #

Instances

Instances details
type XXGRHSs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _1) _2 = NoExtCon

type family XXGRHS x b #

Instances

Instances details
type XXGRHS (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _1) b = NoExtCon

type family XXFunDep x #

Instances

Instances details
type XXFunDep (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXForeignDecl x #

Instances

Instances details
type XXForeignDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXFixitySig x #

Instances

Instances details
type XXFixitySig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XXFieldOcc x #

Instances

Instances details
type XXFieldOcc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXFamilyResultSig x #

Instances

Instances details
type XXFamilyResultSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyDecl x #

Instances

Instances details
type XXFamilyDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXFamEqn x r #

Instances

Instances details
type XXFamEqn (GhcPass _1) r 
Instance details

Defined in GHC.Hs.Decls

type XXFamEqn (GhcPass _1) r = NoExtCon

type family XXExpr x #

Instances

Instances details
type XXExpr GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XXDerivDecl x #

Instances

Instances details
type XXDerivDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXDerivClauseTys x #

Instances

Instances details
type XXDerivClauseTys (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXDefaultDecl x #

Instances

Instances details
type XXDefaultDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXConDeclField x #

Instances

Instances details
type XXConDeclField (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXConDecl x #

Instances

Instances details
type XXConDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXCmdTop x #

Instances

Instances details
type XXCmdTop (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXCmd x #

Instances

Instances details
type XXCmd GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XXClsInstDecl x #

Instances

Instances details
type XXClsInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXBracket x #

Instances

Instances details
type XXBracket (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXApplicativeArg x #

Instances

Instances details
type XXApplicativeArg (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XXAnnDecl x #

Instances

Instances details
type XXAnnDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XXAmbiguousFieldOcc x #

Instances

Instances details
type XXAmbiguousFieldOcc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XXABExport x #

Instances

Instances details
type XXABExport (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XWildPat x #

Instances

Instances details
type XWildPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XWildCardTy x #

Instances

Instances details
type XWildCardTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XWarnings x #

Instances

Instances details
type XWarnings GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XWarnings GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XWarnings GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XWarningD x #

Instances

Instances details
type XWarningD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XWarning x #

Instances

Instances details
type XWarning (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XViewPat x #

Instances

Instances details
type XViewPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XViaStrategy x #

Instances

Instances details
type XViaStrategy GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XVarPat x #

Instances

Instances details
type XVarPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type family XVarBr x #

Instances

Instances details
type XVarBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XVarBind x x' #

Instances

Instances details
type XVarBind (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XVar x #

Instances

Instances details
type XVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField
type XVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField

type family XValD x #

Instances

Instances details
type XValD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XValBinds x x' #

Instances

Instances details
type XValBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XUserTyVar x #

Instances

Instances details
type XUserTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XUntypedSplice x #

Instances

Instances details
type XUntypedSplice (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XUnboundVar x #

Instances

Instances details
type XUnboundVar GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XUnambiguous x #

Instances

Instances details
type XUnambiguous GhcPs 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcRn 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XTypedSplice x #

Instances

Instances details
type XTypedSplice (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XTypeSig x #

Instances

Instances details
type XTypeSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XTypBr x #

Instances

Instances details
type XTypBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XTyVarSig x #

Instances

Instances details
type XTyVarSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XTyVar x #

Instances

Instances details
type XTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XTyLit x #

Instances

Instances details
type XTyLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XTyFamInstD x #

Instances

Instances details
type XTyFamInstD GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XTyClD x #

Instances

Instances details
type XTyClD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XTupleTy x #

Instances

Instances details
type XTupleTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XTuplePat x #

Instances

Instances details
type XTuplePat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XTransStmt x x' b #

Instances

Instances details
type XTransStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type family XTick x #

Instances

Instances details
type XTick (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XTcBracketOut x #

Instances

Instances details
type XTcBracketOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XTExpBr x #

Instances

Instances details
type XTExpBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XSynDecl x #

Instances

Instances details
type XSynDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XSumTy x #

Instances

Instances details
type XSumTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XSumPat x #

Instances

Instances details
type XSumPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]

type family XStockStrategy x #

Instances

Instances details
type XStockStrategy GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XStockStrategy GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XStockStrategy GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XStatic x #

Instances

Instances details
type XStatic GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XStarTy x #

Instances

Instances details
type XStarTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XStandaloneKindSig x #

Instances

Instances details
type XStandaloneKindSig GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XStandaloneKindSig GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XStandaloneKindSig GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XSpliced x #

Instances

Instances details
type XSpliced (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XSpliceTy x #

Instances

Instances details
type XSpliceTy GhcPs 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcRn 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XSplicePat x #

Instances

Instances details
type XSplicePat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type family XSpliceE x #

Instances

Instances details
type XSpliceE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XSpliceDecl x #

Instances

Instances details
type XSpliceDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceD x #

Instances

Instances details
type XSpliceD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XSpecSig x #

Instances

Instances details
type XSpecSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XSpecInstSig x #

Instances

Instances details
type XSpecInstSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XSigPat x #

Instances

Instances details
type XSigPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XSigD x #

Instances

Instances details
type XSigD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XSectionR x #

Instances

Instances details
type XSectionR GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XSectionR GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XSectionR GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XSectionL x #

Instances

Instances details
type XSectionL GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XSectionL GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XSectionL GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XSCCFunSig x #

Instances

Instances details
type XSCCFunSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XSCC x #

Instances

Instances details
type XSCC (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XRuleD x #

Instances

Instances details
type XRuleD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XRuleBndrSig x #

Instances

Instances details
type XRuleBndrSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XRoleAnnotD x #

Instances

Instances details
type XRoleAnnotD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XRnBracketOut x #

Instances

Instances details
type XRnBracketOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XRecordUpd x #

Instances

Instances details
type XRecordUpd GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XRecordCon x #

Instances

Instances details
type XRecordCon GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XRecTy x #

Instances

Instances details
type XRecTy GhcPs 
Instance details

Defined in GHC.Hs.Type

type XRecTy GhcRn 
Instance details

Defined in GHC.Hs.Type

type XRecTy GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XRecStmt x x' b #

Instances

Instances details
type XRecStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type family XRecFld x #

Instances

Instances details
type XRecFld (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XRecFld (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XRec p a = (r :: Type) | r -> a #

GHC's L prefixed variants wrap their vanilla variant in this type family, to add SrcLoc info via Located. Other passes than GhcPass not interested in location information can define this as type instance XRec NoLocated a = a. See Note [XRec and SrcSpans in the AST]

Instances

Instances details
type XRec (GhcPass p) a 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) a = GenLocated (Anno a) a

type family XQuasiQuote x #

Instances

Instances details
type XQuasiQuote (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XQualTy x #

Instances

Instances details
type XQualTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XProjection x #

Instances

Instances details
type XProjection GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XProjection GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XProjection GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XProc x #

Instances

Instances details
type XProc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _1) = EpAnn [AddEpAnn]

type family XPresent x #

Instances

Instances details
type XPresent (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XPragE x #

Instances

Instances details
type XPragE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XPatSynSig x #

Instances

Instances details
type XPatSynSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynBind x x' #

Instances

Instances details
type XPatSynBind (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XPatBr x #

Instances

Instances details
type XPatBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XPatBind x x' #

Instances

Instances details
type XPatBind GhcPs (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcRn (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcTc (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XParTy x #

Instances

Instances details
type XParTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XParStmtBlock x x' #

Instances

Instances details
type XParStmtBlock (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Expr

type family XParStmt x x' b #

Instances

Instances details
type XParStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b = Type

type family XParPat x #

Instances

Instances details
type XParPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type family XPar x #

Instances

Instances details
type XPar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XPSB x x' #

Instances

Instances details
type XPSB (GhcPass idL) GhcPs 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcTc 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet

type family XOverLitE x #

Instances

Instances details
type XOverLitE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XOverLit x #

Instances

Instances details
type XOverLit GhcPs 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcTc 
Instance details

Defined in GHC.Hs.Lit

type family XOverLabel x #

Instances

Instances details
type XOverLabel GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XOverLabel GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XOverLabel GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XOpTy x #

Instances

Instances details
type XOpTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XOpApp x #

Instances

Instances details
type XOpApp GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XNoSig x #

Instances

Instances details
type XNoSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XNewtypeStrategy x #

Instances

Instances details
type XNewtypeStrategy GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XNewtypeStrategy GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XNewtypeStrategy GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XNegApp x #

Instances

Instances details
type XNegApp GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XNegApp GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XNegApp GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XNPlusKPat x #

Instances

Instances details
type XNPlusKPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XNPat x #

Instances

Instances details
type XNPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XMultiIf x #

Instances

Instances details
type XMultiIf GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XMissing x #

Instances

Instances details
type XMissing GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XMinimalSig x #

Instances

Instances details
type XMinimalSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XMG x b #

Instances

Instances details
type XMG GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type family XLitPat x #

Instances

Instances details
type XLitPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type family XLitE x #

Instances

Instances details
type XLitE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XLitE (GhcPass _1) = EpAnnCO

type family XListTy x #

Instances

Instances details
type XListTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XListPat x #

Instances

Instances details
type XListPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XLetStmt x x' b #

Instances

Instances details
type XLetStmt (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = EpAnn [AddEpAnn]

type family XLet x #

Instances

Instances details
type XLet GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XLet GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XLet GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XLazyPat x #

Instances

Instances details
type XLazyPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XLazyPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XLazyPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XLastStmt x x' b #

Instances

Instances details
type XLastStmt (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField

type family XLamCase x #

Instances

Instances details
type XLamCase (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XLam x #

Instances

Instances details
type XLam (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField
type XLam (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField

type family XKindedTyVar x #

Instances

Instances details
type XKindedTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XKindSigD x #

Instances

Instances details
type XKindSigD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XKindSig x #

Instances

Instances details
type XKindSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XInstD x #

Instances

Instances details
type XInstD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XInlineSig x #

Instances

Instances details
type XInlineSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XIf x #

Instances

Instances details
type XIf GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XIf GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XIf GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XIdSig x #

Instances

Instances details
type XIdSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XIParamTy x #

Instances

Instances details
type XIParamTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XIPVar x #

Instances

Instances details
type XIPVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XIPVar (GhcPass _1) = EpAnnCO

type family XIPBinds x #

Instances

Instances details
type XIPBinds GhcPs 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcTc 
Instance details

Defined in GHC.Hs.Binds

type family XIEVar x #

Instances

Instances details
type XIEVar GhcPs 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar GhcRn 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar GhcTc 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingWith x #

Instances

Instances details
type XIEThingWith (GhcPass 'Parsed) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass 'Renamed) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass 'Typechecked) 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAll x #

Instances

Instances details
type XIEThingAll (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAbs x #

Instances

Instances details
type XIEThingAbs (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEModuleContents x #

Instances

Instances details
type XIEModuleContents GhcPs 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents GhcRn 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents GhcTc 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEGroup x #

Instances

Instances details
type XIEGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDocNamed x #

Instances

Instances details
type XIEDocNamed (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDoc x #

Instances

Instances details
type XIEDoc (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type family XHsWordPrim x #

Instances

Instances details
type XHsWordPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsWord64Prim x #

Instances

Instances details
type XHsWord64Prim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsWC x b #

Instances

Instances details
type XHsWC GhcPs b 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b = [Name]
type XHsWC GhcTc b 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcTc b = [Name]

type family XHsValBinds x x' #

Instances

Instances details
type XHsValBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XHsStringPrim x #

Instances

Instances details
type XHsStringPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsString x #

Instances

Instances details
type XHsString (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsSig x #

Instances

Instances details
type XHsSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XHsRule x #

Instances

Instances details
type XHsRule GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XHsRecField x #

Instances

Instances details
type XHsRecField _1 
Instance details

Defined in GHC.Hs.Pat

type family XHsRat x #

Instances

Instances details
type XHsRat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsQTvs x #

Instances

Instances details
type XHsQTvs GhcPs 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcRn 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcRn = HsQTvsRn
type XHsQTvs GhcTc 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcTc = HsQTvsRn

type family XHsPS x #

Instances

Instances details
type XHsPS GhcPs 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcRn 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XHsOuterImplicit x #

Instances

Instances details
type XHsOuterImplicit GhcPs 
Instance details

Defined in GHC.Hs.Type

type XHsOuterImplicit GhcRn 
Instance details

Defined in GHC.Hs.Type

type XHsOuterImplicit GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XHsOuterExplicit x flag #

Instances

Instances details
type XHsOuterExplicit GhcPs _1 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcRn _1 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcTc flag 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag]

type family XHsInteger x #

Instances

Instances details
type XHsInteger (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsIntPrim x #

Instances

Instances details
type XHsIntPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt64Prim x #

Instances

Instances details
type XHsInt64Prim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt x #

Instances

Instances details
type XHsInt (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsIPBinds x x' #

Instances

Instances details
type XHsIPBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XHsForAllVis x #

Instances

Instances details
type XHsForAllVis (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XHsForAllInvis x #

Instances

Instances details
type XHsForAllInvis (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XHsFloatPrim x #

Instances

Instances details
type XHsFloatPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsDoublePrim x #

Instances

Instances details
type XHsDoublePrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsCharPrim x #

Instances

Instances details
type XHsCharPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsChar x #

Instances

Instances details
type XHsChar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type family XHsAnnotation x #

Instances

Instances details
type XHsAnnotation (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XGetField x #

Instances

Instances details
type XGetField GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XGetField GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XGetField GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XFunTy x #

Instances

Instances details
type XFunTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XFunBind x x' #

Instances

Instances details
type XFunBind (GhcPass pL) GhcPs 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcRn 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcTc 
Instance details

Defined in GHC.Hs.Binds

type family XForeignImport x #

Instances

Instances details
type XForeignImport GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XForeignExport x #

Instances

Instances details
type XForeignExport GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XForD x #

Instances

Instances details
type XForD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XForAllTy x #

Instances

Instances details
type XForAllTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XFixitySig x #

Instances

Instances details
type XFixitySig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XFixSig x #

Instances

Instances details
type XFixSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XFamDecl x #

Instances

Instances details
type XFamDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XExprWithTySig x #

Instances

Instances details
type XExprWithTySig GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitTupleTy x #

Instances

Instances details
type XExplicitTupleTy GhcPs 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcRn 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XExplicitTuple x #

Instances

Instances details
type XExplicitTuple GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitSum x #

Instances

Instances details
type XExplicitSum GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitListTy x #

Instances

Instances details
type XExplicitListTy GhcPs 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcRn 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XExplicitList x #

Instances

Instances details
type XExplicitList GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XExpBr x #

Instances

Instances details
type XExpBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XEmptyLocalBinds x x' #

Instances

Instances details
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XDocTy x #

Instances

Instances details
type XDocTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XDocD x #

Instances

Instances details
type XDocD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XDo x #

Instances

Instances details
type XDo GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type

type family XDerivD x #

Instances

Instances details
type XDerivD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XDefD x #

Instances

Instances details
type XDefD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XDecBrL x #

Instances

Instances details
type XDecBrL (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrG x #

Instances

Instances details
type XDecBrG (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XDctSingle x #

Instances

Instances details
type XDctSingle (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XDctMulti x #

Instances

Instances details
type XDctMulti (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XDataFamInstD x #

Instances

Instances details
type XDataFamInstD GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XDataFamInstD GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XDataFamInstD GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XDataDecl x #

Instances

Instances details
type XDataDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XConPat x #

Instances

Instances details
type XConPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XConLikeOut x #

Instances

Instances details
type XConLikeOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XConLikeOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XConDeclH98 x #

Instances

Instances details
type XConDeclH98 (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclGADT x #

Instances

Instances details
type XConDeclGADT (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclField x #

Instances

Instances details
type XConDeclField (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XCompleteMatchSig x #

Instances

Instances details
type XCompleteMatchSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XCoPat x #

type family XCmdWrap x #

Instances

Instances details
type XCmdWrap (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XCmdTop x #

Instances

Instances details
type XCmdTop GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdPar x #

Instances

Instances details
type XCmdPar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLet x #

Instances

Instances details
type XCmdLet GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLamCase x #

Instances

Instances details
type XCmdLamCase (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLam x #

Instances

Instances details
type XCmdLam (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XCmdIf x #

Instances

Instances details
type XCmdIf GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdDo x #

Instances

Instances details
type XCmdDo GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdCase x #

Instances

Instances details
type XCmdCase GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrForm x #

Instances

Instances details
type XCmdArrForm GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrApp x #

Instances

Instances details
type XCmdArrApp GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCmdApp x #

Instances

Instances details
type XCmdApp (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCmdApp (GhcPass _1) = EpAnnCO

type family XClsInstD x #

Instances

Instances details
type XClsInstD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XClassOpSig x #

Instances

Instances details
type XClassOpSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XClassDecl x #

Instances

Instances details
type XClassDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XCase x #

Instances

Instances details
type XCase GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XCase GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XCase GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XCTyFamInstDecl x #

Instances

Instances details
type XCTyFamInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCTyClGroup x #

Instances

Instances details
type XCTyClGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleDecls x #

Instances

Instances details
type XCRuleDecls GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleBndr x #

Instances

Instances details
type XCRuleBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCRoleAnnotDecl x #

Instances

Instances details
type XCRoleAnnotDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XCMatch x b #

Instances

Instances details
type XCMatch (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b = EpAnn [AddEpAnn]

type family XCKindSig x #

Instances

Instances details
type XCKindSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCInjectivityAnn x #

Instances

Instances details
type XCInjectivityAnn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCImportDecl x #

Instances

Instances details
type XCImportDecl GhcPs 
Instance details

Defined in GHC.Hs.ImpExp

type XCImportDecl GhcRn 
Instance details

Defined in GHC.Hs.ImpExp

type XCImportDecl GhcTc 
Instance details

Defined in GHC.Hs.ImpExp

type family XCIPBind x #

Instances

Instances details
type XCIPBind (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type family XCHsGroup x #

Instances

Instances details
type XCHsGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCHsFieldLabel x #

Instances

Instances details
type XCHsFieldLabel (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XCHsDerivingClause x #

Instances

Instances details
type XCHsDerivingClause (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCHsDataDefn x #

Instances

Instances details
type XCHsDataDefn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCGRHSs x b #

Instances

Instances details
type XCGRHSs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type family XCGRHS x b #

Instances

Instances details
type XCGRHS (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type XCGRHS (GhcPass _1) _2 = EpAnn GrhsAnn

type family XCFunDep x #

Instances

Instances details
type XCFunDep (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCFieldOcc x #

Instances

Instances details
type XCFieldOcc GhcPs 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcRn 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XCFamilyDecl x #

Instances

Instances details
type XCFamilyDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCFamEqn x r #

Instances

Instances details
type XCFamEqn (GhcPass _1) r 
Instance details

Defined in GHC.Hs.Decls

type XCFamEqn (GhcPass _1) r = EpAnn [AddEpAnn]

type family XCDerivDecl x #

Instances

Instances details
type XCDerivDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XCDefaultDecl x #

Instances

Instances details
type XCDefaultDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XCClsInstDecl x #

Instances

Instances details
type XCClsInstDecl GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XCClsInstDecl GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XCClsInstDecl GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XBracket x #

Instances

Instances details
type XBracket (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XBodyStmt x x' b #

Instances

Instances details
type XBodyStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b = Type

type family XBindStmt x x' b #

Instances

Instances details
type XBindStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type family XBinTick x #

Instances

Instances details
type XBinTick (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XBangTy x #

Instances

Instances details
type XBangTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XBangPat x #

Instances

Instances details
type XBangPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XBangPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XBangPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XAsPat x #

Instances

Instances details
type XAsPat GhcPs 
Instance details

Defined in GHC.Hs.Pat

type XAsPat GhcRn 
Instance details

Defined in GHC.Hs.Pat

type XAsPat GhcTc 
Instance details

Defined in GHC.Hs.Pat

type family XArithSeq x #

Instances

Instances details
type XArithSeq GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeStmt x x' b #

Instances

Instances details
type XApplicativeStmt (GhcPass _1) GhcPs b 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcRn b 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcTc b 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgOne x #

Instances

Instances details
type XApplicativeArgOne GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgMany x #

Instances

Instances details
type XApplicativeArgMany (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type family XAppTypeE x #

Instances

Instances details
type XAppTypeE GhcPs 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcRn 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcTc 
Instance details

Defined in GHC.Hs.Expr

type family XAppTy x #

Instances

Instances details
type XAppTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XAppKindTy x #

Instances

Instances details
type XAppKindTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type family XApp x #

Instances

Instances details
type XApp (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _1) = EpAnnCO

type family XAnyClassStrategy x #

Instances

Instances details
type XAnyClassStrategy GhcPs 
Instance details

Defined in GHC.Hs.Decls

type XAnyClassStrategy GhcRn 
Instance details

Defined in GHC.Hs.Decls

type XAnyClassStrategy GhcTc 
Instance details

Defined in GHC.Hs.Decls

type family XAnnD x #

Instances

Instances details
type XAnnD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type family XAmbiguous x #

Instances

Instances details
type XAmbiguous GhcPs 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcRn 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcTc 
Instance details

Defined in GHC.Hs.Type

type family XAbsBinds x x' #

Instances

Instances details
type XAbsBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type family XABE x #

Instances

Instances details
type XABE (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

class WrapXRec p a where #

The trivial wrapper that carries no additional information See Note [XRec and SrcSpans in the AST]

Methods

wrapXRec :: a -> XRec p a #

class UnXRec p where #

We can strip off the XRec to access the underlying data. See Note [XRec and SrcSpans in the AST]

Methods

unXRec :: XRec p a -> a #

Instances

Instances details
UnXRec (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

Methods

unXRec :: XRec (GhcPass p) a -> a #

type family NoGhcTc p #

See Note [NoGhcTc] in GHC.Hs.Extension. It has to be in this module because it is used like an extension point (in the data definitions of types that should be parameter-agnostic.

Instances

Instances details
type NoGhcTc (GhcPass pass)

Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur. See Note [NoGhcTc]

Instance details

Defined in GHC.Hs.Extension

type NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass)

data NoExtField #

A placeholder type for TTG extension points that are not currently unused to represent any particular value.

This should not be confused with NoExtCon, which are found in unused extension constructors and therefore should never be inhabited. In contrast, NoExtField is used in extension points (e.g., as the field of some constructor), so it must have an inhabitant to construct AST passes that manipulate fields with that extension point as their type.

Constructors

NoExtField 

Instances

Instances details
Data NoExtField 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtField -> c NoExtField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtField #

toConstr :: NoExtField -> Constr #

dataTypeOf :: NoExtField -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtField) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtField) #

gmapT :: (forall b. Data b => b -> b) -> NoExtField -> NoExtField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r #

gmapQ :: (forall d. Data d => d -> u) -> NoExtField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField #

Outputable NoExtField 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtField -> SDoc #

Eq NoExtField 
Instance details

Defined in Language.Haskell.Syntax.Extension

Ord NoExtField 
Instance details

Defined in Language.Haskell.Syntax.Extension

ToHie (Context (Located NoExtField)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located NoExtField) -> HieM [HieAST Type]

data NoExtCon #

Used in TTG extension constructors that have yet to be extended with anything. If an extension constructor has NoExtCon as its field, it is not intended to ever be constructed anywhere, and any function that consumes the extension constructor can eliminate it by way of noExtCon.

This should not be confused with NoExtField, which are found in unused extension points (not constructors) and therefore can be inhabited.

Instances

Instances details
Data NoExtCon 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtCon -> c NoExtCon #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtCon #

toConstr :: NoExtCon -> Constr #

dataTypeOf :: NoExtCon -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtCon) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtCon) #

gmapT :: (forall b. Data b => b -> b) -> NoExtCon -> NoExtCon #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r #

gmapQ :: (forall d. Data d => d -> u) -> NoExtCon -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtCon -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon #

Outputable NoExtCon 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtCon -> SDoc #

Eq NoExtCon 
Instance details

Defined in Language.Haskell.Syntax.Extension

Ord NoExtCon 
Instance details

Defined in Language.Haskell.Syntax.Extension

class MapXRec p where #

We can map over the underlying type contained in an XRec while preserving the annotation as is.

Methods

mapXRec :: Anno a ~ Anno b => (a -> b) -> XRec p a -> XRec p b #

Instances

Instances details
MapXRec (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

Methods

mapXRec :: Anno a ~ Anno b => (a -> b) -> XRec (GhcPass p) a -> XRec (GhcPass p) b #

type LIdP p = XRec p (IdP p) #

type family IdP p #

Maps the "normal" id type for a given pass

Instances

Instances details
type IdP (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p

type family Anno a = (b :: Type) #

Instances

Instances details
type Anno ConLike 
Instance details

Defined in GHC.Hs.Pat

type Anno OverlapMode 
Instance details

Defined in GHC.Hs.Decls

type Anno OverlapMode 
Instance details

Defined in GHC.Hs.Decls

type Anno CType 
Instance details

Defined in GHC.Hs.Decls

type Anno Name 
Instance details

Defined in GHC.Hs.Extension

type Anno RdrName 
Instance details

Defined in GHC.Hs.Extension

type Anno StringLiteral 
Instance details

Defined in GHC.Hs.Binds

type Anno Id 
Instance details

Defined in GHC.Hs.Extension

type Anno ModuleName 
Instance details

Defined in GHC.Hs.ImpExp

type Anno DocDecl 
Instance details

Defined in GHC.Hs.Decls

type Anno HsIPName 
Instance details

Defined in GHC.Hs.Type

type Anno Bool 
Instance details

Defined in GHC.Hs.Decls

type Anno (IE (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IE (GhcPass p)) = SrcSpanAnnA
type Anno (ImportDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedA (IE (GhcPass p))) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno (FixitySig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

type Anno (IPBind (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

type Anno (Sig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

type Anno (AnnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (ClsInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (ConDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (DataFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (DefaultDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivClauseTys (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivStrategy (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamilyDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamilyResultSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (ForeignDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FunDep (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (HsDecl (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (HsDerivingClause (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (InjectivityAnn (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (InstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (RoleAnnotDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleBndr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SpliceDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (StandaloneKindSig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (TyClDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (TyFamInstDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (WarnDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (WarnDecls (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

type Anno (HsCmd (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsCmdTop (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsExpr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsSplice (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsOverLit (GhcPass p)) 
Instance details

Defined in GHC.Hs.Pat

type Anno (Pat (GhcPass p)) 
Instance details

Defined in GHC.Hs.Pat

type Anno (AmbiguousFieldOcc GhcTc) 
Instance details

Defined in GHC.Hs.Pat

type Anno (BangType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (ConDeclField (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (FieldOcc (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsKind (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsSigType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (IE (GhcPass p))] 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (ConDeclField (GhcPass _1))] 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) 
Instance details

Defined in GHC.Hs.Binds

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsRecField (GhcPass p) arg) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' p arg) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) = SrcSpanAnnA
type Anno (HsTyVarBndr _flag GhcPs) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcRn) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcTc) 
Instance details

Defined in GHC.Hs.Type

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) 
Instance details

Defined in GHC.Hs.Expr

noExtField :: NoExtField #

Used when constructing a term with an unused extension point.

noExtCon :: NoExtCon -> a #

Eliminate a NoExtCon. Much like absurd.

data SrcUnpackedness #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{-# UNPACK #-} specified

SrcNoUnpack

{-# NOUNPACK #-} specified

NoSrcUnpack

no unpack pragma

Instances

Instances details
Data SrcUnpackedness 
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) -> SrcUnpackedness -> c SrcUnpackedness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness #

toConstr :: SrcUnpackedness -> Constr #

dataTypeOf :: SrcUnpackedness -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcUnpackedness) #

gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness #

Binary SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: SrcUnpackedness -> SDoc #

Eq SrcUnpackedness 
Instance details

Defined in GHC.Core.DataCon

data SrcStrictness #

Source Strictness

What strictness annotation the user wrote

Constructors

SrcLazy

Lazy, ie ~

SrcStrict

Strict, ie !

NoSrcStrict

no strictness annotation

Instances

Instances details
Data SrcStrictness 
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) -> SrcStrictness -> c SrcStrictness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcStrictness #

toConstr :: SrcStrictness -> Constr #

dataTypeOf :: SrcStrictness -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcStrictness) #

gmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcStrictness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcStrictness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness #

Binary SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: SrcStrictness -> SDoc #

Eq SrcStrictness 
Instance details

Defined in GHC.Core.DataCon

data HsSrcBang #

Haskell Source Bang

Bangs on data constructor arguments as the user wrote them in the source code.

(HsSrcBang _ SrcUnpack SrcLazy) and (HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we emit a warning (in checkValidDataCon) and treat it like (HsSrcBang _ NoSrcUnpack SrcLazy)

Instances

Instances details
Data HsSrcBang 
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) -> HsSrcBang -> c HsSrcBang #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang #

toConstr :: HsSrcBang -> Constr #

dataTypeOf :: HsSrcBang -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) #

gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang #

Outputable HsSrcBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc #

data HsImplBang #

Haskell Implementation Bang

Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.

Constructors

HsLazy

Lazy field, or one with an unlifted type

HsStrict

Strict but not unpacked field

HsUnpack (Maybe Coercion)

Strict and unpacked field co :: arg-ty ~ product-ty HsBang

Instances

Instances details
Data HsImplBang 
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) -> HsImplBang -> c HsImplBang #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImplBang #

toConstr :: HsImplBang -> Constr #

dataTypeOf :: HsImplBang -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImplBang) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang) #

gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplBang -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang #

Outputable HsImplBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc #

type Mult = Type #

Mult is a type alias for Type.

Mult must contain Type because multiplicity variables are mere type variables (of kind Multiplicity) in Haskell. So the simplest implementation is to make Mult be Type.

Multiplicities can be formed with: - One: GHC.Types.One (= oneDataCon) - Many: GHC.Types.Many (= manyDataCon) - Multiplication: GHC.Types.MultMul (= multMulTyCon)

So that Mult feels a bit more structured, we provide pattern synonyms and smart constructors for these.

data SpliceExplicitFlag #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances

Instances details
Data SpliceExplicitFlag 
Instance details

Defined in GHC.Types.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceExplicitFlag -> c SpliceExplicitFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag #

toConstr :: SpliceExplicitFlag -> Constr #

dataTypeOf :: SpliceExplicitFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpliceExplicitFlag) #

gmapT :: (forall b. Data b => b -> b) -> SpliceExplicitFlag -> SpliceExplicitFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag #

data TcEvBinds #

Instances

Instances details
Data TcEvBinds 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcEvBinds -> c TcEvBinds #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcEvBinds #

toConstr :: TcEvBinds -> Constr #

dataTypeOf :: TcEvBinds -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcEvBinds) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcEvBinds) #

gmapT :: (forall b. Data b => b -> b) -> TcEvBinds -> TcEvBinds #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r #

gmapQ :: (forall d. Data d => d -> u) -> TcEvBinds -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TcEvBinds -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds #

Outputable TcEvBinds 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc #

ToHie (EvBindContext (LocatedA TcEvBinds)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: EvBindContext (LocatedA TcEvBinds) -> HieM [HieAST Type]

data QuoteWrapper #

Constructors

QuoteWrapper EvVar Type 

Instances

Instances details
Data QuoteWrapper 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteWrapper #

toConstr :: QuoteWrapper -> Constr #

dataTypeOf :: QuoteWrapper -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteWrapper) #

gmapT :: (forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r #

gmapQ :: (forall d. Data d => d -> u) -> QuoteWrapper -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper #

data HsWrapper #

Instances

Instances details
Data HsWrapper 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWrapper -> c HsWrapper #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsWrapper #

toConstr :: HsWrapper -> Constr #

dataTypeOf :: HsWrapper -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsWrapper) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsWrapper) #

gmapT :: (forall b. Data b => b -> b) -> HsWrapper -> HsWrapper #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWrapper -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWrapper -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper #

Outputable HsWrapper 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HsWrapper -> SDoc #

ToHie (LocatedA HsWrapper) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA HsWrapper -> HieM [HieAST Type]

data HoleExprRef #

Where to store evidence for expression holes See Note [Holes] in GHC.Tc.Types.Constraint

Constructors

HER 

Fields

  • (IORef EvTerm)

    where to write the erroring expression

  • TcType

    expected type of that expression

  • Unique

    for debug output only

Instances

Instances details
Data HoleExprRef 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HoleExprRef -> c HoleExprRef #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HoleExprRef #

toConstr :: HoleExprRef -> Constr #

dataTypeOf :: HoleExprRef -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HoleExprRef) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HoleExprRef) #

gmapT :: (forall b. Data b => b -> b) -> HoleExprRef -> HoleExprRef #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HoleExprRef -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HoleExprRef -> r #

gmapQ :: (forall d. Data d => d -> u) -> HoleExprRef -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HoleExprRef -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef #

Outputable HoleExprRef 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HoleExprRef -> SDoc #

data EvTypeable #

Instructions on how to make a Typeable dictionary. See Note [Typeable evidence terms]

Constructors

EvTypeableTyCon TyCon [EvTerm]

Dictionary for Typeable T where T is a type constructor with all of its kind variables saturated. The [EvTerm] is Typeable evidence for the applied kinds..

EvTypeableTyApp EvTerm EvTerm

Dictionary for Typeable (s t), given a dictionaries for s and t.

EvTypeableTrFun EvTerm EvTerm EvTerm

Dictionary for Typeable (s # w -> t), given a dictionaries for w, s, and t.

EvTypeableTyLit EvTerm

Dictionary for a type literal, e.g. Typeable "foo" or Typeable 3 The EvTerm is evidence of, e.g., KnownNat 3 (see #10348)

Instances

Instances details
Data EvTypeable 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTypeable -> c EvTypeable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTypeable #

toConstr :: EvTypeable -> Constr #

dataTypeOf :: EvTypeable -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTypeable) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable) #

gmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r #

gmapQ :: (forall d. Data d => d -> u) -> EvTypeable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTypeable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable #

Outputable EvTypeable 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTypeable -> SDoc #

data EvTerm #

Instances

Instances details
Data EvTerm 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTerm -> c EvTerm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTerm #

toConstr :: EvTerm -> Constr #

dataTypeOf :: EvTerm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTerm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm) #

gmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r #

gmapQ :: (forall d. Data d => d -> u) -> EvTerm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTerm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm #

Outputable EvTerm 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTerm -> SDoc #

data EvCallStack #

Evidence for CallStack implicit parameters.

Constructors

EvCsEmpty 
EvCsPushCall Name RealSrcSpan EvExpr

EvCsPushCall name loc stk represents a call to name, occurring at loc, in a calling context stk.

Instances

Instances details
Data EvCallStack 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvCallStack -> c EvCallStack #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvCallStack #

toConstr :: EvCallStack -> Constr #

dataTypeOf :: EvCallStack -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvCallStack) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvCallStack) #

gmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r #

gmapQ :: (forall d. Data d => d -> u) -> EvCallStack -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvCallStack -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack #

Outputable EvCallStack 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvCallStack -> SDoc #

data EvBindsVar #

Instances

Instances details
Uniquable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindsVar -> SDoc #

newtype EvBindMap #

Constructors

EvBindMap 

Instances

Instances details
Outputable EvBindMap 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindMap -> SDoc #

data EvBind #

Constructors

EvBind 

Instances

Instances details
Outputable EvBind 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBind -> SDoc #

wrapIP :: Type -> CoercionR #

Create a Expr that wraps a value in an implicit-parameter dictionary. See unwrapIP.

unwrapIP :: Type -> CoercionR #

Create a Expr that unwraps an implicit-parameter or overloaded-label dictionary to expose the underlying value. We expect the Expr to have the form `IP sym ty` or `IsLabel sym ty`, and return a Expr `co :: IP sym ty ~ ty` or `co :: IsLabel sym ty ~ ty`. See also Note [Type-checking overloaded labels] in GHC.Tc.Gen.Expr.

nonDetStrictFoldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a #

mkTcAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [TcType] -> [TcCoercion] -> TcCoercion #

maybeTcSymCo :: SwapFlag -> TcCoercion -> TcCoercion #

If a SwapFlag is IsSwapped, flip the orientation of a coercion

maybeTcSubCo :: HasDebugCallStack => EqRel -> TcCoercionN -> TcCoercion #

If the EqRel is ReprEq, makes a SubCo; otherwise, does nothing. Note that the input coercion should always be nominal.

isTcReflexiveCo :: TcCoercion -> Bool #

This version does a slow check, calculating the related types and seeing if they are equal.

hsWrapDictBinders :: HsWrapper -> Bag DictId #

Identifies the lambda-bound dictionaries of an HsWrapper. This is used (only) to allow the pattern-match overlap checker to know what Given dictionaries are in scope.

We specifically do not collect dictionaries bound in a WpLet. These are either superclasses of lambda-bound ones, or (extremely numerous) results of binding Wanted dictionaries. We definitely don't want all those cluttering up the Given dictionaries for pattern-match overlap checking!

foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a #

evSelector :: Id -> [Type] -> [EvExpr] -> EvExpr #

evId :: EvId -> EvExpr #

Any sort of evidence Id, including coercions

evCast :: EvExpr -> TcCoercion -> EvTerm #

d |> co

applyQuoteWrapper :: QuoteWrapper -> HsWrapper #

Convert the QuoteWrapper into a normal HsWrapper which can be used to apply its contents.

data CoercionHole #

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Instances

Instances details
Data CoercionHole 
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) -> CoercionHole -> c CoercionHole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoercionHole #

toConstr :: CoercionHole -> Constr #

dataTypeOf :: CoercionHole -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoercionHole) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoercionHole) #

gmapT :: (forall b. Data b => b -> b) -> CoercionHole -> CoercionHole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r #

gmapQ :: (forall d. Data d => d -> u) -> CoercionHole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoercionHole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole #

Uniquable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: CoercionHole -> SDoc #

data Role #

Instances

Instances details
Data Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role #

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) #

gmapT :: (forall b. Data b => b -> b) -> Role -> Role #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r #

gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role #

Binary Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

put_ :: BinHandle -> Role -> IO () #

put :: BinHandle -> Role -> IO (Bin Role) #

get :: BinHandle -> IO Role #

Outputable Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc #

Eq Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

data LeftOrRight #

Constructors

CLeft 
CRight 

Instances

Instances details
Data LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight #

toConstr :: LeftOrRight -> Constr #

dataTypeOf :: LeftOrRight -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) #

gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r #

gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight #

Binary LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Outputable LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc #

Eq LeftOrRight 
Instance details

Defined in GHC.Types.Basic

pickLR :: LeftOrRight -> (a, a) -> a #

mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #

The mapAndUnzipM function maps its first argument over a list, returning the result as a pair of lists. This function is mainly used with complicated data structures or a state monad.

foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b #

Right-to-left monadic fold over the elements of a structure.

Given a structure t with elements (a, b, c, ..., x, y), the result of a fold with an operator function f is equivalent to:

foldrM f z t = do
    yy <- f y z
    xx <- f x yy
    ...
    bb <- f b cc
    aa <- f a bb
    return aa -- Just @return z@ when the structure is empty

For a Monad m, given two functions f1 :: a -> m b and f2 :: b -> m c, their Kleisli composition (f1 >=> f2) :: a -> m c is defined by:

(f1 >=> f2) a = f1 a >>= f2

Another way of thinking about foldrM is that it amounts to an application to z of a Kleisli composition:

foldrM f z t = f y >=> f x >=> ... >=> f b >=> f a $ z

The monadic effects of foldrM are sequenced from right to left, and e.g. folds of infinite lists will diverge.

If at some step the bind operator (>>=) short-circuits (as with, e.g., mzero in a MonadPlus), the evaluated effects will be from a tail of the element sequence. If you want to evaluate the monadic effects in left-to-right order, or perhaps be able to short-circuit after an initial sequence of elements, you'll need to use foldlM instead.

If the monadic effects don't short-circuit, the outermost application of f is to the leftmost element a, so that, ignoring effects, the result looks like a right fold:

a `f` (b `f` (c `f` (... (x `f` (y `f` z))))).

Examples

Expand

Basic usage:

>>> let f i acc = do { print i ; return $ i : acc }
>>> foldrM f [] [0..3]
3
2
1
0
[0,1,2,3]

foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #

Left-to-right monadic fold over the elements of a structure.

Given a structure t with elements (a, b, ..., w, x, y), the result of a fold with an operator function f is equivalent to:

foldlM f z t = do
    aa <- f z a
    bb <- f aa b
    ...
    xx <- f ww x
    yy <- f xx y
    return yy -- Just @return z@ when the structure is empty

For a Monad m, given two functions f1 :: a -> m b and f2 :: b -> m c, their Kleisli composition (f1 >=> f2) :: a -> m c is defined by:

(f1 >=> f2) a = f1 a >>= f2

Another way of thinking about foldlM is that it amounts to an application to z of a Kleisli composition:

foldlM f z t =
    flip f a >=> flip f b >=> ... >=> flip f x >=> flip f y $ z

The monadic effects of foldlM are sequenced from left to right.

If at some step the bind operator (>>=) short-circuits (as with, e.g., mzero in a MonadPlus), the evaluated effects will be from an initial segment of the element sequence. If you want to evaluate the monadic effects in right-to-left order, or perhaps be able to short-circuit after processing a tail of the sequence of elements, you'll need to use foldrM instead.

If the monadic effects don't short-circuit, the outermost application of f is to the rightmost element y, so that, ignoring effects, the result looks like a left fold:

((((z `f` a) `f` b) ... `f` w) `f` x) `f` y

Examples

Expand

Basic usage:

>>> let f a e = do { print e ; return $ e : a }
>>> foldlM f [] [0..3]
0
1
2
3
[3,2,1,0]

data IsExtraConstraint #

Instances

Instances details
Outputable IsExtraConstraint 
Instance details

Defined in GHC.Tc.Utils.Monad

xoptM :: Extension -> TcRnIf gbl lcl Bool #

writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () #

wrapLocSndMA :: (a -> TcM (b, c)) -> LocatedA a -> TcM (b, LocatedA c) #

wrapLocSndM :: (a -> TcM (b, c)) -> Located a -> TcM (b, Located c) #

wrapLocM_ :: (a -> TcM ()) -> Located a -> TcM () #

wrapLocMA_ :: (a -> TcM ()) -> LocatedA a -> TcM () #

wrapLocMA :: (a -> TcM b) -> GenLocated (SrcSpanAnn' ann) a -> TcRn (GenLocated (SrcSpanAnn' ann) b) #

wrapLocM :: (a -> TcM b) -> Located a -> TcM (Located b) #

wrapLocFstMA :: (a -> TcM (b, c)) -> LocatedA a -> TcM (LocatedA b, c) #

wrapLocFstM :: (a -> TcM (b, c)) -> Located a -> TcM (Located b, c) #

wrapLocAM :: (a -> TcM b) -> LocatedAn an a -> TcM (Located b) #

woptM :: WarningFlag -> TcRnIf gbl lcl Bool #

withoutDynamicNow :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

withException :: TcRnIf gbl lcl (MaybeErr SDoc a) -> TcRnIf gbl lcl a #

A convenient wrapper for taking a MaybeErr SDoc a and throwing an exception if it is an error.

withDynamicNow :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

whenXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #

whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #

whenNoErrs :: TcM () -> TcM () #

whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #

whenDOptM :: DumpFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #

Do it flag is true

warnTcM :: WarnReason -> Bool -> (TidyEnv, SDoc) -> TcM () #

Display a warning if a condition is met.

warnTc :: WarnReason -> Bool -> SDoc -> TcM () #

Display a warning if a condition is met.

warnIfFlag :: WarningFlag -> Bool -> SDoc -> TcRn () #

Display a warning if a condition is met, and the warning is enabled

warnIf :: Bool -> SDoc -> TcRn () #

Display a warning if a condition is met.

updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl () #

Update the external package state.

This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.

updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a #

Update the external package state. Returns the second result of the modifier function.

This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.

updTopEnv :: (HscEnv -> HscEnv) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

updTcRef :: TcRef a -> (a -> a) -> TcRnIf gbl lcl () #

updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

unsetXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

unlessXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #

traceTc :: String -> SDoc -> TcRn () #

traceRn :: String -> SDoc -> TcRn () #

traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () #

traceIf :: SDoc -> TcRnIf m n () #

traceHiDiffs :: SDoc -> TcRnIf m n () #

tcScalingUsage :: Mult -> TcM a -> TcM a #

tcScalingUsage mult thing_inside runs thing_inside and scales all the usage information by mult.

tcCollectingUsage :: TcM a -> TcM (UsageEnv, a) #

tcCollectingUsage thing_inside runs thing_inside and returns the usage information which was collected as part of the execution of thing_inside. Careful: tcCollectingUsage thing_inside itself does not report any usage information, it's up to the caller to incorporate the returned usage information into the larger context appropriately.

setXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

setTcLevel :: TcLevel -> TcM a -> TcM a #

setStage :: ThStage -> TcM a -> TcRn a #

setSrcSpanA :: SrcSpanAnn' ann -> TcRn a -> TcRn a #

setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a #

setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a #

setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a #

setCtLocM :: CtLoc -> TcM a -> TcM a #

recoverM :: TcRn r -> TcRn r -> TcRn r #

recordUnsafeInfer :: WarningMessages -> TcM () #

Mark that safe inference has failed See Note [Safe Haskell Overlapping Instances Implementation] although this is used for more than just that failure case.

readTcRef :: TcRef a -> TcRnIf gbl lcl a #

pushTcLevelsM :: Int -> TcM a -> TcM (a, TcLevel) #

pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) #

The name says it all. The returned TcLevel is the *inner* TcLevel.

printForUserTcRn :: SDoc -> TcRn () #

Like logInfoTcRn, but for user consumption

popErrCtxt :: TcM a -> TcM a #

newTcRef :: a -> TcRnIf gbl lcl (TcRef a) #

newNoTcEvBinds :: TcM EvBindsVar #

Creates an EvBindsVar incapable of holding any bindings. It still tracks covar usages (see comments on ebv_tcvs in GHC.Tc.Types.Evidence), thus must be made monadically

mkDecoratedSDocAt #

Arguments

:: SrcSpan 
-> SDoc

The important part of the message

-> SDoc

The context of the message

-> SDoc

Any supplementary information.

-> TcRn (MsgEnvelope DecoratedSDoc) 

mapAndReportM :: (a -> TcRn b) -> [a] -> TcRn [b] #

Apply the function to all elements on the input list If all succeed, return the list of results Otherwise fail, propagating all errors

mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b] #

Drop elements of the input that fail, so the result list can be shorter than the argument list

keepAlive :: Name -> TcRn () #

initTcWithGbl :: HscEnv -> TcGblEnv -> RealSrcSpan -> TcM r -> IO (Messages DecoratedSDoc, Maybe r) #

Run a TcM action in the context of an existing GblEnv.

initTcRnIf #

Arguments

:: Char

Mask for unique supply

-> HscEnv 
-> gbl 
-> lcl 
-> TcRnIf gbl lcl a 
-> IO a 

initTc :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> TcM r -> IO (Messages DecoratedSDoc, Maybe r) #

Setup the initial typechecking environment

initIfaceTcRn :: IfG a -> TcRn a #

Run an IfG (top-level interface monad) computation inside an existing TcRn (typecheck-renaming monad) computation by initializing an IfGblEnv based on TcGblEnv.

initIfaceLoad :: HscEnv -> IfG a -> IO a #

initIfaceLclWithSubst :: Module -> SDoc -> IsBootInterface -> NameShape -> IfL a -> IfM lcl a #

Initialize interface typechecking, but with a NameShape to apply when typechecking top-level OccNames (see lookupIfaceTop)

initIfaceCheck :: SDoc -> HscEnv -> IfG a -> IO a #

ifErrsM :: TcRn r -> TcRn r -> TcRn r #

goptM :: GeneralFlag -> TcRnIf gbl lcl Bool #

getLclEnv :: TcRnIf gbl lcl lcl #

getGblEnv :: TcRnIf gbl lcl gbl #

getEnvs :: TcRnIf gbl lcl (gbl, lcl) #

getCCIndexM :: (gbl -> TcRef CostCentreState) -> FastString -> TcRnIf gbl lcl CostCentreIndex #

Get the next cost centre index associated with a given name.

forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a) #

Run thing_inside in an interleaved thread. It shares everything with the parent thread, so this is DANGEROUS.

It returns Nothing if the computation fails

It's used for lazily type-checking interface signatures, which is pretty benign.

See Note [Masking exceptions in forkM_maybe]

forkM :: SDoc -> IfL a -> IfL a #

foldAndRecoverM :: (b -> a -> TcRn b) -> b -> [a] -> TcRn b #

The accumulator is not updated if the action fails

fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst] #

Switch instances to safe instances if we're in Safe mode.

finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode #

Figure out the final correct safe haskell mode

failIfTcM :: Bool -> (TidyEnv, SDoc) -> TcM () #

failIfTc :: Bool -> SDoc -> TcM () #

failIfM :: SDoc -> IfL a #

failAt :: SrcSpan -> SDoc -> TcRn a #

extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a #

emitSimples :: Cts -> TcM () #

emitSimple :: Ct -> TcM () #

emitHole :: Hole -> TcM () #

dumpTcRn :: Bool -> DumpFlag -> String -> DumpFormat -> SDoc -> TcRn () #

Unconditionally dump some trace output

Certain tests (T3017, Roles3, T12763 etc.) expect part of the output generated by `-ddump-types` to be in PprUser style. However, generally we want all other debugging output to use PprDump style. We PprUser style if useUserStyle is True.

dumpOptTcRn :: DumpFlag -> String -> DumpFormat -> SDoc -> TcRn () #

Dump if the given DumpFlag is set.

doptM :: DumpFlag -> TcRnIf gbl lcl Bool #

discardResult :: TcM a -> TcM () #

discardConstraints :: TcM a -> TcM a #

Throw out any constraints emitted by the thing_inside

debugTc :: TcM () -> TcM () #

checkTcM :: Bool -> (TidyEnv, SDoc) -> TcM () #

checkTc :: Bool -> SDoc -> TcM () #

checkNoErrs :: TcM r -> TcM r #

checkErr :: Bool -> SDoc -> TcRn () #

attemptM :: TcRn r -> TcRn (Maybe r) #

askNoErrs :: TcRn a -> TcRn (a, Bool) #

add_warn :: WarnReason -> SDoc -> SDoc -> TcRn () #

Display a warning, with an optional flag, for the current source location.

addWarnTcM :: WarnReason -> (TidyEnv, SDoc) -> TcM () #

Display a warning in a given context.

addWarnTc :: WarnReason -> SDoc -> TcM () #

Display a warning in the current context.

addWarnAt :: WarnReason -> SrcSpan -> SDoc -> TcRn () #

Display a warning for a given source location.

addWarn :: WarnReason -> SDoc -> TcRn () #

Display a warning for the current source location.

addModFinalizersWithLclEnv :: ThModFinalizers -> TcM () #

Adds the given modFinalizers to the global environment and set them to use the current local environment.

addLocMA :: (a -> TcM b) -> GenLocated (SrcSpanAnn' ann) a -> TcM b #

addLocM :: (a -> TcM b) -> Located a -> TcM b #

addLandmarkErrCtxtM :: (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a #

Variant of addLandmarkErrCtxt that allows for monadic operations and tidying.

addLandmarkErrCtxt :: SDoc -> TcM a -> TcM a #

Add a fixed landmark message to the error context. A landmark message is always sure to be reported, even if there is a lot of context. It also doesn't count toward the maximum number of contexts reported.

addErrs :: [(SrcSpan, SDoc)] -> TcRn () #

addErrTcM :: (TidyEnv, SDoc) -> TcM () #

addErrTc :: SDoc -> TcM () #

addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a #

Add a message to the error context. This message may do tidying.

addErrCtxt :: SDoc -> TcM a -> TcM a #

Add a fixed message to the error context. This message should not do any tidying.

addErrAt :: SrcSpan -> SDoc -> TcRn () #

addErr :: SDoc -> TcRn () #

data WhereFrom #

Instances

Instances details
Outputable WhereFrom 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc #

data ThStage #

Instances

Instances details
Outputable ThStage 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: ThStage -> SDoc #

type ThLevel = Int #

data TcTyThing #

A typecheckable thing available in a local context. Could be AGlobal TyThing, but also lexically scoped variables, etc. See GHC.Tc.Utils.Env for how to retrieve a TyThing given a Name.

Instances

Instances details
Outputable TcTyThing 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcTyThing -> SDoc #

data TcSigInfo #

Instances

Instances details
Outputable TcSigInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcSigInfo -> SDoc #

type TcRnIf a b = IOEnv (Env a b) #

type TcRef a = IORef a #

Type alias for IORef; the convention is we'll use this for mutable bits of data in TcGblEnv which are updated during typechecking and returned at the end.

data TcPluginResult #

Constructors

TcPluginContradiction [Ct]

The plugin found a contradiction. The returned constraints are removed from the inert set, and recorded as insoluble.

TcPluginOk [(EvTerm, Ct)] [Ct]

The first field is for constraints that were solved. These are removed from the inert set, and the evidence for them is recorded. The second field contains new work, that should be processed by the constraint solver.

data TcPluginM a #

Instances

Instances details
MonadFail TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

fail :: String -> TcPluginM a #

Applicative TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

pure :: a -> TcPluginM a #

(<*>) :: TcPluginM (a -> b) -> TcPluginM a -> TcPluginM b #

liftA2 :: (a -> b -> c) -> TcPluginM a -> TcPluginM b -> TcPluginM c #

(*>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

(<*) :: TcPluginM a -> TcPluginM b -> TcPluginM a #

Functor TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

fmap :: (a -> b) -> TcPluginM a -> TcPluginM b #

(<$) :: a -> TcPluginM b -> TcPluginM a #

Monad TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

(>>=) :: TcPluginM a -> (a -> TcPluginM b) -> TcPluginM b #

(>>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

return :: a -> TcPluginM a #

data TcPlugin #

Constructors

TcPlugin 

Fields

type TcM = TcRn #

Historical "type-checking monad" (now it's just TcRn).

data TcIdSigInst #

Instances

Instances details
Outputable TcIdSigInst 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInst -> SDoc #

data TcIdSigInfo #

Instances

Instances details
Outputable TcIdSigInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInfo -> SDoc #

type TcIdSet = IdSet #

type TcId = Id #

data TcGblEnv #

TcGblEnv describes the top-level of the module at the point at which the typechecker is finished work. It is this structure that is handed on to the desugarer For state that needs to be updated during the typechecking phase and returned at end, use a TcRef (= IORef).

Constructors

TcGblEnv 

Fields

Instances

Instances details
ContainsModule TcGblEnv 
Instance details

Defined in GHC.Tc.Types

data TcBinder #

Instances

Instances details
HasOccName TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

occName :: TcBinder -> OccName #

Outputable TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcBinder -> SDoc #

type THDocs = Map DocLoc String #

The current collection of docs that Template Haskell has built up via putDoc.

data SpliceType #

Constructors

Typed 
Untyped 

data SelfBootInfo #

Constructors

NoSelfBoot 
SelfBoot 

type RnM = TcRn #

Historical "renaming monad" (now it's just TcRn).

data NameShape #

A NameShape is a substitution on Names that can be used to refine the identities of a hole while we are renaming interfaces (see GHC.Iface.Rename). Specifically, a NameShape for ns_module_name A, defines a mapping from {A.T} (for some OccName T) to some arbitrary other Name.

The most intruiging thing about a NameShape, however, is how it's constructed. A NameShape is *implied* by the exported AvailInfos of the implementor of an interface: if an implementor of signature <H> exports M.T, you implicitly define a substitution from {H.T} to M.T. So a NameShape is computed from the list of AvailInfos that are exported by the implementation of a module, or successively merged together by the export lists of signatures which are joining together.

It's not the most obvious way to go about doing this, but it does seem to work!

NB: Can't boot this and put it in NameShape because then we start pulling in too many DynFlags things.

data IsGroupClosed #

IsGroupClosed describes a group of mutually-recursive bindings

data ImportAvails #

ImportAvails summarises what was imported from where, irrespective of whether the imported things are actually used or not. It is used:

  • when processing the export list,
  • when constructing usage info for the interface file,
  • to identify the list of directly imported modules for initialisation purposes and for optimised overlap checking of family instances,
  • when figuring out what things are really unused

Constructors

ImportAvails 

Fields

  • imp_mods :: ImportedMods

    Domain is all directly-imported modules

    See the documentation on ImportedModsVal in GHC.Unit.Module.Imported for the meaning of the fields.

    We need a full ModuleEnv rather than a ModuleNameEnv here, because we might be importing modules of the same name from different packages. (currently not the case, but might be in the future).

  • imp_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot

    Home-package modules needed by the module being compiled

    It doesn't matter whether any of these dependencies are actually used when compiling the module; they are listed if they are below it at all. For example, suppose M imports A which imports X. Then compiling M might not need to consult X.hi, but X is still listed in M's dependencies.

  • imp_dep_pkgs :: Set UnitId

    Packages needed by the module being compiled, whether directly, or via other modules in this package, or via modules imported from other packages.

  • imp_trust_pkgs :: Set UnitId

    This is strictly a subset of imp_dep_pkgs and records the packages the current module needs to trust for Safe Haskell compilation to succeed. A package is required to be trusted if we are dependent on a trustworthy module in that package. While perhaps making imp_dep_pkgs a tuple of (UnitId, Bool) where True for the bool indicates the package is required to be trusted is the more logical design, doing so complicates a lot of code not concerned with Safe Haskell. See Note [Tracking Trust Transitively] in GHC.Rename.Names

  • imp_trust_own_pkg :: Bool

    Do we require that our own package is trusted? This is to handle efficiently the case where a Safe module imports a Trustworthy module that resides in the same package as it. See Note [Trust Own Package] in GHC.Rename.Names

  • imp_orphs :: [Module]

    Orphan modules below us in the import tree (and maybe including us for imported modules)

  • imp_finsts :: [Module]

    Family instance modules below us in the import tree (and maybe including us for imported modules)

type IfM lcl = TcRnIf IfGblEnv lcl #

type IfL = IfM IfLclEnv #

data IfGblEnv #

Constructors

IfGblEnv 

type IfG = IfM () #

data IdBindingInfo #

IdBindingInfo describes how an Id is bound.

It is used for the following purposes: a) for static forms in checkClosedInStaticForm and b) to figure out when a nested binding can be generalised, in decideGeneralisationPlan.

Instances

Instances details
Outputable IdBindingInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: IdBindingInfo -> SDoc #

data FrontendResult #

FrontendResult describes the result of running the frontend of a Haskell module. Currently one always gets a FrontendTypecheck, since running the frontend involves typechecking a program. hs-sig merges are not handled here.

This data type really should be in GHC.Driver.Env, but it needs to have a TcGblEnv which is only defined here.

type ErrCtxt = (Bool, TidyEnv -> TcM (TidyEnv, SDoc)) #

data Env gbl lcl #

Constructors

Env 

Fields

Instances

Instances details
ContainsHooks (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractHooks :: Env gbl lcl -> Hooks #

ContainsDynFlags (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractDynFlags :: Env gbl lcl -> DynFlags #

ContainsModule gbl => ContainsModule (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractModule :: Env gbl lcl -> Module #

ContainsLogger (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractLogger :: Env gbl lcl -> Logger #

data DocLoc #

This is a mirror of Template Haskell's DocLoc, but the TH names are resolved to GHC names.

Instances

Instances details
Eq DocLoc 
Instance details

Defined in GHC.Tc.Types

Methods

(==) :: DocLoc -> DocLoc -> Bool #

(/=) :: DocLoc -> DocLoc -> Bool #

Ord DocLoc 
Instance details

Defined in GHC.Tc.Types

unsafeTcPluginTcM :: TcM a -> TcPluginM a #

This function provides an escape for direct access to the TcM monad. It should not be used lightly, and the provided TcPluginM API should be favoured instead.

plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails #

Union two ImportAvails

This function is a key part of Import handling, basically for each import we create a separate ImportAvails structure and then union them all together with this function.

lintGblEnv :: Logger -> DynFlags -> TcGblEnv -> TcM () #

Check the TcGblEnv for consistency. Currently, only checks axioms, but should check other aspects, too.

hasCompleteSig :: TcSigFun -> Name -> Bool #

No signature or a partial signature

getPlatform :: TcM Platform #

Get target platform

getEvBindsTcPluginM :: TcPluginM EvBindsVar #

Access the EvBindsVar carried by the TcPluginM during constraint solving. Returns Nothing if invoked during tcPluginInit or tcPluginStop.

data IOEnv env a #

Instances

Instances details
MonadFail (IOEnv m) 
Instance details

Defined in GHC.Data.IOEnv

Methods

fail :: String -> IOEnv m a #

MonadFix (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

mfix :: (a -> IOEnv env a) -> IOEnv env a #

MonadIO (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

liftIO :: IO a -> IOEnv env a #

Alternative (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

empty :: IOEnv env a #

(<|>) :: IOEnv env a -> IOEnv env a -> IOEnv env a #

some :: IOEnv env a -> IOEnv env [a] #

many :: IOEnv env a -> IOEnv env [a] #

Applicative (IOEnv m) 
Instance details

Defined in GHC.Data.IOEnv

Methods

pure :: a -> IOEnv m a #

(<*>) :: IOEnv m (a -> b) -> IOEnv m a -> IOEnv m b #

liftA2 :: (a -> b -> c) -> IOEnv m a -> IOEnv m b -> IOEnv m c #

(*>) :: IOEnv m a -> IOEnv m b -> IOEnv m b #

(<*) :: IOEnv m a -> IOEnv m b -> IOEnv m a #

Functor (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

fmap :: (a -> b) -> IOEnv env a -> IOEnv env b #

(<$) :: a -> IOEnv env b -> IOEnv env a #

Monad (IOEnv m) 
Instance details

Defined in GHC.Data.IOEnv

Methods

(>>=) :: IOEnv m a -> (a -> IOEnv m b) -> IOEnv m b #

(>>) :: IOEnv m a -> IOEnv m b -> IOEnv m b #

return :: a -> IOEnv m a #

MonadPlus (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

mzero :: IOEnv env a #

mplus :: IOEnv env a -> IOEnv env a -> IOEnv env a #

MonadCatch (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

catch :: Exception e => IOEnv env a -> (e -> IOEnv env a) -> IOEnv env a #

MonadMask (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

mask :: ((forall a. IOEnv env a -> IOEnv env a) -> IOEnv env b) -> IOEnv env b #

uninterruptibleMask :: ((forall a. IOEnv env a -> IOEnv env a) -> IOEnv env b) -> IOEnv env b #

generalBracket :: IOEnv env a -> (a -> ExitCase b -> IOEnv env c) -> (a -> IOEnv env b) -> IOEnv env (b, c) #

MonadThrow (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

throwM :: Exception e => e -> IOEnv env a #

ContainsHooks env => HasHooks (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

getHooks :: IOEnv env Hooks #

ContainsDynFlags env => HasDynFlags (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

getDynFlags :: IOEnv env DynFlags #

ContainsModule env => HasModule (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

getModule :: IOEnv env Module #

ContainsLogger env => HasLogger (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

getLogger :: IOEnv env Logger #

writeMutVar :: IORef a -> a -> IOEnv env () #

updMutVarM :: IORef a -> (a -> IOEnv env a) -> IOEnv env () #

updMutVar :: IORef a -> (a -> a) -> IOEnv env () #

updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a #

Perform a computation with an altered environment

unsafeInterleaveM :: IOEnv env a -> IOEnv env a #

tryM :: IOEnv env r -> IOEnv env (Either IOEnvFailure r) #

tryAllM :: IOEnv env r -> IOEnv env (Either SomeException r) #

setEnv :: env' -> IOEnv env' a -> IOEnv env a #

Perform a computation with a different environment

runIOEnv :: env -> IOEnv env a -> IO a #

readMutVar :: IORef a -> IOEnv env a #

newMutVar :: a -> IOEnv env (IORef a) #

getEnv :: IOEnv env env #

fixM :: (a -> IOEnv env a) -> IOEnv env a #

failWithM :: String -> IOEnv env a #

failM :: IOEnv env a #

atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b #

Strict variant of atomicUpdMutVar.

atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b #

Atomically update the reference. Does not force the evaluation of the new variable contents. For strict update, use atomicUpdMutVar'.

data CompleteMatch #

A list of conlikes which represents a complete pattern match. These arise from COMPLETE signatures. See also Note [Implementation of COMPLETE pragmas].

Instances

Instances details
Outputable CompleteMatch 
Instance details

Defined in GHC.Types.CompleteMatch

Methods

ppr :: CompleteMatch -> SDoc #

zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d]) #

zipWith4M :: Monad m => (a -> b -> c -> d -> m e) -> [a] -> [b] -> [c] -> [d] -> m [e] #

zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m () #

zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d] #

whenM :: Monad m => m Bool -> m () -> m () #

Monadic version of when, taking the condition in the monad

unlessM :: Monad m => m Bool -> m () -> m () #

Monadic version of unless, taking the condition in the monad

orM :: Monad m => m Bool -> m Bool -> m Bool #

Monadic version of or

maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

Monadic version of fmap specialised for Maybe

mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] #

Monadic version of mapSnd

mapAndUnzip5M :: Monad m => (a -> m (b, c, d, e, f)) -> [a] -> m ([b], [c], [d], [e], [f]) #

mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e]) #

mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d]) #

mapAndUnzipM for triples

mapAccumLM #

Arguments

:: Monad m 
=> (acc -> x -> m (acc, y))

combining function

-> acc

initial state

-> [x]

inputs

-> m (acc, [y])

final state, outputs

Monadic version of mapAccumL

liftSndM :: Monad m => (a -> b) -> m (r, a) -> m (r, b) #

liftFstM :: Monad m => (a -> b) -> m (a, r) -> m (b, r) #

foldlM_ :: (Monad m, Foldable t) => (a -> b -> m a) -> a -> t b -> m () #

Monadic version of foldl that discards its result

fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

Monadic version of fmap

fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d) #

Monadic version of fmap

filterOutM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #

Like filterM, only it reverses the sense of the test.

data ForeignSrcLang #

Foreign formats supported by GHC via TH

Constructors

LangC

C

LangCxx

C++

LangObjc

Objective C

LangObjcxx

Objective C++

LangAsm

Assembly language (.s)

RawObject

Object (.o)

Instances

Instances details
Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Eq ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-9.2.4" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))

data BuiltInSyntax #

BuiltInSyntax is for things like (:), [] and tuples, which have special syntactic forms. They aren't in scope as such.

Constructors

BuiltInSyntax 
UserSyntax 

stableNameCmp :: Name -> Name -> Ordering #

Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.

pprNameUnqualified :: Name -> SDoc #

Print the string of Name unqualifiedly directly.

nameStableString :: Name -> String #

Get a string representation of a Name that's unique and stable across recompilations. Used for deterministic generation of binds for derived instances. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"

nameIsLocalOrFrom :: Module -> Name -> Bool #

Returns True if the name is (a) Internal (b) External but from the specified module (c) External but from the interactive package

The key idea is that False means: the entity is defined in some other module you can find the details (type, fixity, instances) in some interface file those details will be stored in the EPT or HPT

True means: the entity is defined in this module or earlier in the GHCi session you can find details (type, fixity, instances) in the TcGblEnv or TcLclEnv

The isInteractiveModule part is because successive interactions of a GHCi session each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come from the magic interactive package; and all the details are kept in the TcLclEnv, TcGblEnv, NOT in the HPT or EPT. See Note [The interactive package] in GHC.Runtime.Context

nameIsFromExternalPackage :: HomeUnit -> Name -> Bool #

Returns True if the Name comes from some other package: neither this package nor the interactive package.

mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name #

Create a name which is actually defined by the compiler itself

mkSystemName :: Unique -> OccName -> Name #

Create a name brought into being by the compiler

mkInternalName :: Unique -> OccName -> SrcSpan -> Name #

Create a name which is (for now at least) local to the current module and hence does not need a Module to disambiguate it from other Names

mkFCallName :: Unique -> String -> Name #

Make a name for a foreign call

mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name #

Create a name which definitely originates in the given module

localiseName :: Name -> Name #

Make the Name into an internal name, regardless of what it was to begin with

isWiredIn :: NamedThing thing => thing -> Bool #

isDynLinkName :: Platform -> Module -> Name -> Bool #

Will the Name come from a dynamically linked package?

data OccEnv a #

Instances

Instances details
Data a => Data (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccEnv a -> c (OccEnv a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OccEnv a) #

toConstr :: OccEnv a -> Constr #

dataTypeOf :: OccEnv a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OccEnv a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OccEnv a)) #

gmapT :: (forall b. Data b => b -> b) -> OccEnv a -> OccEnv a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r #

gmapQ :: (forall d. Data d => d -> u) -> OccEnv a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OccEnv a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) #

Outputable a => Outputable (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc #

unitOccEnv :: OccName -> a -> OccEnv a #

startsWithUnderscore :: OccName -> Bool #

Haskell 98 encourages compilers to suppress warnings about unused names in a pattern if they start with _: this implements that test

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc #

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #

parenSymOcc :: OccName -> SDoc -> SDoc #

Wrap parens around an operator

occEnvElts :: OccEnv a -> [a] #

mkSuperDictSelOcc #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a #

mkOccEnv :: [(OccName, a)] -> OccEnv a #

mkLocalOcc #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

mkInstTyTcOcc #

Arguments

:: String

Family name, e.g. Map

-> OccSet

avoid these Occs

-> OccName
R:Map

Derive a name for the representation type constructor of a data/newtype instance.

mkDFunOcc #

Arguments

:: String

Typically the class and type glommed together e.g. OrdMaybe. Only used in debug mode, for extra clarity

-> Bool

Is this a hs-boot instance DFun?

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b #

isValOcc :: OccName -> Bool #

Value OccNamess are those that are either in the variable or data constructor namespaces

isTypeableBindOcc :: OccName -> Bool #

Is an OccName one of a Typeable TyCon or Module binding? This is needed as these bindings are renamed differently. See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.

isSymOcc :: OccName -> Bool #

Test if the OccName is that for any operator (whether it is a data constructor or variable or whatever)

isDerivedOccName :: OccName -> Bool #

Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints

isDataSymOcc :: OccName -> Bool #

Test if the OccName is a data constructor that starts with a symbol (e.g. :, or [])

foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #

filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b #

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #

alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt #

class NamedThing a where #

A class allowing convenient access to the Name of various datatypes

Minimal complete definition

getName

Methods

getOccName :: a -> OccName #

getName :: a -> Name #

Instances

Instances details
NamedThing Class 
Instance details

Defined in GHC.Core.Class

NamedThing ConLike 
Instance details

Defined in GHC.Core.ConLike

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

NamedThing PatSyn 
Instance details

Defined in GHC.Core.PatSyn

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

NamedThing IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

NamedThing HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

NamedThing Name 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

NamedThing (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

NamedThing (Located a) => NamedThing (LocatedAn an a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

data Name #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Instances details
Data Name 
Instance details

Defined in GHC.Types.Name

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

NFData Name 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () #

NamedThing Name 
Instance details

Defined in GHC.Types.Name

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Binary Name

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

Methods

put_ :: BinHandle -> Name -> IO () #

put :: BinHandle -> Name -> IO (Bin Name) #

get :: BinHandle -> IO Name #

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc #

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

Eq Name

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

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 #

ModifyState Name 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Name -> Name -> HieState -> HieState

ToHie (LBooleanFormula (LocatedN Name)) 
Instance details

Defined in Compat.HieAst

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

type Anno Name 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type FastStringEnv a = UniqFM FastString a #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.

data OccName #

Occurrence Name

In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"

Instances

Instances details
Data OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName #

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) #

gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r #

gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName #

Show OccName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Binary OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc #

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Eq OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

(==) :: OccName -> OccName -> Bool #

(/=) :: OccName -> OccName -> Bool #

Ord OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Hashable OccName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

hashWithSalt :: Int -> OccName -> Int #

hash :: OccName -> Int #

class HasOccName name where #

Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.

Methods

occName :: name -> OccName #

Instances

Instances details
HasOccName IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceDecl -> OccName #

HasOccName HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

HasOccName TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

occName :: TcBinder -> OccName #

HasOccName GreName 
Instance details

Defined in GHC.Types.Avail

Methods

occName :: GreName -> OccName #

HasOccName FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

HasOccName GlobalRdrElt 
Instance details

Defined in GHC.Types.Name.Reader

HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

HasOccName name => HasOccName (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

occName :: IEWrappedName name -> OccName #

data RdrName #

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

Orig Module OccName

Original name

An original name; the module is the defining module. This is used when GHC generates code that will be fed into the renamer (e.g. from deriving clauses), but where we want to say "Use Prelude.map dammit". One of these can be created with mkOrig

Exact Name

Exact name

We know exactly the Name. This is used:

  1. When the parser parses built-in syntax like [] and (,), but wants a RdrName from it
  2. By Template Haskell, when TH has generated a unique name

Such a RdrName can be created by using getRdrName on a Name

Instances

Instances details
Data RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName #

toConstr :: RdrName -> Constr #

dataTypeOf :: RdrName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) #

gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r #

gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName #

DisambInfixOp RdrName 
Instance details

Defined in GHC.Parser.PostProcess

HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

Outputable RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc #

OutputableBndr RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Eq RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

(==) :: RdrName -> RdrName -> Bool #

(/=) :: RdrName -> RdrName -> Bool #

Ord RdrName 
Instance details

Defined in GHC.Types.Name.Reader

type Anno RdrName 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

data Parent #

See Note [Parents]

Constructors

NoParent 
ParentIs 

Fields

Instances

Instances details
Data Parent 
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) -> Parent -> c Parent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parent #

toConstr :: Parent -> Constr #

dataTypeOf :: Parent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Parent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent) #

gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r #

gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parent -> m Parent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent #

Outputable Parent 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: Parent -> SDoc #

Eq Parent 
Instance details

Defined in GHC.Types.Name.Reader

Methods

(==) :: Parent -> Parent -> Bool #

(/=) :: Parent -> Parent -> Bool #

data LocalRdrEnv #

Local Reader Environment See Note [LocalRdrEnv]

Instances

Instances details
Outputable LocalRdrEnv 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LocalRdrEnv -> SDoc #

data ImportSpec #

Import Specification

The ImportSpec of something says how it came to be imported It's quite elaborate so that we can give accurate unused-name warnings.

Constructors

ImpSpec 

Instances

Instances details
Data ImportSpec 
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) -> ImportSpec -> c ImportSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec #

toConstr :: ImportSpec -> Constr #

dataTypeOf :: ImportSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) #

gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec #

Outputable ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc #

Eq ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

data ImpItemSpec #

Import Item Specification

Describes import info a particular Name

Constructors

ImpAll

The import had no import list, or had a hiding list

ImpSome

The import had an import list. The is_explicit field is True iff the thing was named explicitly in the import specs rather than being imported as part of a "..." group. Consider:

import C( T(..) )

Here the constructors of T are not named explicitly; only T is named explicitly.

Instances

Instances details
Data ImpItemSpec 
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) -> ImpItemSpec -> c ImpItemSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpItemSpec #

toConstr :: ImpItemSpec -> Constr #

dataTypeOf :: ImpItemSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpItemSpec) #

gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec #

Eq ImpItemSpec 
Instance details

Defined in GHC.Types.Name.Reader

data ImpDeclSpec #

Import Declaration Specification

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

  • is_mod :: ModuleName

    Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

  • is_as :: ModuleName

    Import alias, e.g. from as M (or Muggle if there is no as clause)

  • is_qual :: Bool

    Was this import qualified?

  • is_dloc :: SrcSpan

    The location of the entire import declaration

Instances

Instances details
Data ImpDeclSpec 
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) -> ImpDeclSpec -> c ImpDeclSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec #

toConstr :: ImpDeclSpec -> Constr #

dataTypeOf :: ImpDeclSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) #

gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec #

Eq ImpDeclSpec 
Instance details

Defined in GHC.Types.Name.Reader

type GlobalRdrEnv = OccEnv [GlobalRdrElt] #

Global Reader Environment

Keyed by OccName; when looking up a qualified name we look up the OccName part, and then check the Provenance to see if the appropriate qualification is valid. This saves routinely doubling the size of the env by adding both qualified and unqualified names to the domain.

The list in the codomain is required because there may be name clashes These only get reported on lookup, not on construction

INVARIANT 1: All the members of the list have distinct gre_name fields; that is, no duplicate Names

INVARIANT 2: Imported provenance => Name is an ExternalName However LocalDefs can have an InternalName. This happens only when type-checking a [d| ... |] Template Haskell quotation; see this note in GHC.Rename.Names Note [Top-level Names in Template Haskell decl quotes]

INVARIANT 3: If the GlobalRdrEnv maps [occ -> gre], then greOccName gre = occ

NB: greOccName gre is usually the same as nameOccName (greMangledName gre), but not always in the case of record selectors; see Note [GreNames]

data GlobalRdrElt #

Global Reader Element

An element of the GlobalRdrEnv

Instances

Instances details
Data GlobalRdrElt 
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) -> GlobalRdrElt -> c GlobalRdrElt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalRdrElt #

toConstr :: GlobalRdrElt -> Constr #

dataTypeOf :: GlobalRdrElt -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalRdrElt) #

gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt #

HasOccName GlobalRdrElt 
Instance details

Defined in GHC.Types.Name.Reader

Outputable GlobalRdrElt 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: GlobalRdrElt -> SDoc #

Eq GlobalRdrElt 
Instance details

Defined in GHC.Types.Name.Reader

unQualSpecOK :: ImportSpec -> Bool #

Is in scope unqualified?

unQualOK :: GlobalRdrElt -> Bool #

Test if an unqualified version of this thing would be in scope

transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv #

Apply a transformation function to the GREs for these OccNames

starInfo :: Bool -> RdrName -> SDoc #

Display info about the treatment of * under NoStarIsType.

With StarIsType, three properties of * hold:

(a) it is not an infix operator (b) it is always in scope (c) it is a synonym for Data.Kind.Type

However, the user might not know that they are working on a module with NoStarIsType and write code that still assumes (a), (b), and (c), which actually do not hold in that module.

Violation of (a) shows up in the parser. For instance, in the following examples, we have * not applied to enough arguments:

data A :: * data F :: * -> *

Violation of (b) or (c) show up in the renamer and the typechecker respectively. For instance:

type K = Either * Bool

This will parse differently depending on whether StarIsType is enabled, but it will parse nonetheless. With NoStarIsType it is parsed as a type operator, thus we have ((*) Either Bool). Now there are two cases to consider:

  1. There is no definition of (*) in scope. In this case the renamer will fail to look it up. This is a violation of assumption (b).
  2. There is a definition of the (*) type operator in scope (for example coming from GHC.TypeNats). In this case the user will get a kind mismatch error. This is a violation of assumption (c).

The user might unknowingly be working on a module with NoStarIsType or use * as Type out of habit. So it is important to give a hint whenever an assumption about * is violated. Unfortunately, it is somewhat difficult to deal with (c), so we limit ourselves to (a) and (b).

starInfo generates an appropriate hint to the user depending on the extensions enabled in the module and the name that triggered the error. That is, if we have NoStarIsType and the error is related to * or its Unicode variant, the resulting SDoc will contain a helpful suggestion. Otherwise it is empty.

qualSpecOK :: ModuleName -> ImportSpec -> Bool #

Is in scope qualified with the given module?

pprNameProvenance :: GlobalRdrElt -> SDoc #

Print out one place where the name was define/imported (With -dppr-debug, print them all)

pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)] #

Pick GREs that are in scope *both* qualified *and* unqualified Return each GRE that is, as a pair (qual_gre, unqual_gre) These two GREs are the original GRE with imports filtered to express how it is in scope qualified an unqualified respectively

Used only for the 'module M' item in export list; see exports_from_avail

pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] #

Takes a list of GREs which have the right OccName x Pick those GREs that are in scope * Qualified, as x if want_qual is Qual M _ * Unqualified, as x if want_unqual is Unqual _

Return each such GRE, with its ImportSpecs filtered, to reflect how it is in scope qualified or unqualified respectively. See Note [GRE filtering]

opIsAt :: RdrName -> Bool #

Indicate if the given name is the "@" operator

mkQual :: NameSpace -> (FastString, FastString) -> RdrName #

Make a qualified RdrName in the given namespace and where the ModuleName and the OccName are taken from the first and second elements of the tuple respectively

lookupGRE_RdrName' :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] #

Look for this RdrName in the global environment. Includes record fields without selector functions (see Note [NoFieldSelectors] in GHC.Rename.Env).

lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] #

Look for this RdrName in the global environment. Omits record fields without selector functions (see Note [NoFieldSelectors] in GHC.Rename.Env).

lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt #

Look for precisely this Name in the environment, but with an OccName that might differ from that of the Name. See lookupGRE_FieldLabel and Note [GreNames].

lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt #

Look for precisely this Name in the environment. This tests whether it is in scope, ignoring anything else that might be in scope with the same OccName.

lookupGRE_GreName :: GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt #

Look for precisely this GreName in the environment. This tests whether it is in scope, ignoring anything else that might be in scope with the same OccName.

lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt #

Look for a particular record field selector in the environment, where the selector name and field label may be different: the GlobalRdrEnv is keyed on the label. See Note [GreNames] for why this happens.

isNoFieldSelectorGRE :: GlobalRdrElt -> Bool #

Is this a record field defined with NoFieldSelectors? (See Note [NoFieldSelectors] in GHC.Rename.Env)

isFieldSelectorGRE :: GlobalRdrElt -> Bool #

Is this a record field defined with FieldSelectors? (See Note [NoFieldSelectors] in GHC.Rename.Env)

isDuplicateRecFldGRE :: GlobalRdrElt -> Bool #

Is this a record field defined with DuplicateRecordFields? (See Note [GreNames])

gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo] #

Takes a list of distinct GREs and folds them into AvailInfos. This is more efficient than mapping each individual GRE to an AvailInfo and the folding using plusAvail but needs the uniqueness assumption.

gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] #

make a GlobalRdrEnv where all the elements point to the same Provenance (useful for "hiding" imports, or imports with no details).

grePrintableName :: GlobalRdrElt -> Name #

A Name for the GRE suitable for output to the user. Its OccName will be the greOccName (see Note [GreNames]).

greOccName :: GlobalRdrElt -> OccName #

See Note [GreNames]

greMangledName :: GlobalRdrElt -> Name #

A Name for the GRE for internal use. Careful: the OccName of this Name is not necessarily the same as the greOccName (see Note [GreNames]).

greFieldLabel :: GlobalRdrElt -> Maybe FieldLabel #

Returns the field label of this GRE, if it has one

greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan #

The SrcSpan of the name pointed to by the GRE.

greDefinitionModule :: GlobalRdrElt -> Maybe Module #

The module in which the name pointed to by the GRE is defined.

getRdrName :: NamedThing thing => thing -> RdrName #

data GreName #

Used where we may have an ordinary name or a record field label. See Note [GreNames] in GHC.Types.Name.Reader.

Instances

Instances details
Data GreName 
Instance details

Defined in GHC.Types.Avail

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GreName -> c GreName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GreName #

toConstr :: GreName -> Constr #

dataTypeOf :: GreName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GreName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GreName) #

gmapT :: (forall b. Data b => b -> b) -> GreName -> GreName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GreName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GreName -> r #

gmapQ :: (forall d. Data d => d -> u) -> GreName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GreName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GreName -> m GreName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GreName -> m GreName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GreName -> m GreName #

HasOccName GreName 
Instance details

Defined in GHC.Types.Avail

Methods

occName :: GreName -> OccName #

Binary GreName 
Instance details

Defined in GHC.Types.Avail

Outputable GreName 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: GreName -> SDoc #

Eq GreName 
Instance details

Defined in GHC.Types.Avail

Methods

(==) :: GreName -> GreName -> Bool #

(/=) :: GreName -> GreName -> Bool #

data Severity #

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 
Instance details

Defined in GHC.Types.Error

ToJson Severity 
Instance details

Defined in GHC.Types.Error

Methods

json :: Severity -> JsonDoc #

Eq Severity 
Instance details

Defined in GHC.Types.Error

greNamePrintableName :: GreName -> Name #

A Name suitable for output to the user. For fields, the OccName will be the field label. See Note [GreNames] in GHC.Types.Name.Reader.

data SourceModified #

Indicates whether a given module's source has been modified since it was last compiled.

Constructors

SourceModified

the source has been modified

SourceUnmodified

the source has not been modified. Compilation may or may not be necessary, depending on whether any dependencies have changed since we last compiled.

SourceUnmodifiedAndStable

the source has not been modified, and furthermore all of its (transitive) dependencies are up to date; it definitely does not need to be recompiled. This is important for two reasons: (a) we can omit the version check in checkOldIface, and (b) if the module used TH splices we don't need to force recompilation.

data HscSource #

Constructors

HsSrcFile

.hs file

HsBootFile

.hs-boot file

HsigFile

.hsig file

Instances

Instances details
Show HscSource 
Instance details

Defined in GHC.Types.SourceFile

Binary HscSource 
Instance details

Defined in GHC.Types.SourceFile

Eq HscSource 
Instance details

Defined in GHC.Types.SourceFile

Ord HscSource 
Instance details

Defined in GHC.Types.SourceFile

data Var #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
Data Var 
Instance details

Defined in GHC.Types.Var

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var #

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) #

gmapT :: (forall b. Data b => b -> b) -> Var -> Var #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r #

gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var #

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc #

Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

ModifyState Id 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Id -> Id -> HieState -> HieState

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

type Anno Id 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

class HasModule (m :: Type -> Type) where #

Methods

getModule :: m Module #

Instances

Instances details
ContainsModule env => HasModule (IOEnv env) 
Instance details

Defined in GHC.Data.IOEnv

Methods

getModule :: IOEnv env Module #

class ContainsModule t where #

Methods

extractModule :: t -> Module #

Instances

Instances details
ContainsModule DsGblEnv 
Instance details

Defined in GHC.HsToCore.Types

ContainsModule TcGblEnv 
Instance details

Defined in GHC.Tc.Types

ContainsModule gbl => ContainsModule (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractModule :: Env gbl lcl -> Module #

uninstantiateInstantiatedUnit :: InstantiatedUnit -> InstantiatedUnit #

Remove instantiations of the given instantiated unit

uninstantiateInstantiatedModule :: InstantiatedModule -> InstantiatedModule #

Remove instantiations of the given module instantiated unit

stableModuleCmp :: Module -> Module -> Ordering #

This gives a stable ordering, as opposed to the Ord instance which gives an ordering based on the Uniques of the components, which may not be stable from run to run of the compiler.

moduleStableString :: Module -> String #

Get a string representation of a Module that's unique and stable across recompilations. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"

moduleIsDefinite :: Module -> Bool #

A Module is definite if it has no free holes.

mkHoleModule :: ModuleName -> GenModule (GenUnit u) #

Create a hole Module

isHoleModule :: GenModule (GenUnit u) -> Bool #

Test if a Module is not instantiated

installedModuleEq :: InstalledModule -> Module -> Bool #

Test if a Module corresponds to a given InstalledModule, modulo instantiation.

getUnitInstantiations :: Unit -> (UnitId, Maybe InstantiatedUnit) #

Return the unit-id this unit is an instance of and the module instantiations (if any).

getModuleInstantiation :: Module -> (InstalledModule, Maybe InstantiatedModule) #

Given a possibly on-the-fly instantiated module, split it into a Module that we definitely can find on-disk, as well as an instantiation if we need to instantiate it on the fly. If the instantiation is Nothing no on-the-fly renaming is needed.

type ModuleSet = Set NDModule #

A set of Modules

type ModuleNameEnv elt = UniqFM ModuleName elt #

A map keyed off of ModuleNames (actually, their Uniques)

data ModuleEnv elt #

A map keyed off of Modules

data InstalledModuleEnv elt #

A map keyed off of InstalledModule

type DModuleNameEnv elt = UniqDFM ModuleName elt #

A map keyed off of ModuleNames (actually, their Uniques) Has deterministic folds and can be deterministically converted to a list

plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a #

mkModuleEnv :: [(Module, a)] -> ModuleEnv a #

mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b #

extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a #

extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a #

removeBootSuffix :: FilePath -> FilePath #

Remove the -boot suffix to .hs, .hi and .o files

addBootSuffix_maybe :: IsBootInterface -> FilePath -> FilePath #

Add the -boot suffix if the Bool argument is True

addBootSuffixLocn :: ModLocation -> ModLocation #

Add the -boot suffix to all file paths associated with the module

addBootSuffix :: FilePath -> FilePath #

Add the -boot suffix to .hs, .hi and .o files

newtype UnitKey #

A unit key in the database

Constructors

UnitKey FastString 

Instances

Instances details
IsUnitId UnitKey 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: UnitKey -> FastString #

class IsUnitId u where #

Class for types that are used as unit identifiers (UnitKey, UnitId, Unit)

We need this class because we create new unit ids for virtual units (see VirtUnit) and they have to to be made from units with different kinds of identifiers.

Methods

unitFS :: u -> FastString #

Instances

Instances details
IsUnitId UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: UnitId -> FastString #

IsUnitId UnitKey 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: UnitKey -> FastString #

IsUnitId unit => IsUnitId (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Definite unit -> FastString #

IsUnitId u => IsUnitId (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: GenUnit u -> FastString #

IsUnitId unit => IsUnitId (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Indefinite unit -> FastString #

data IsBootInterface #

Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsBootInterface #

toConstr :: IsBootInterface -> Constr #

dataTypeOf :: IsBootInterface -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsBootInterface) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsBootInterface) #

gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> IsBootInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface #

Show IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Binary IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Eq IsBootInterface 
Instance details

Defined in GHC.Unit.Types

Ord IsBootInterface 
Instance details

Defined in GHC.Unit.Types

type InstalledModule = GenModule UnitId #

A InstalledModule is a Module whose unit is identified with an UnitId.

data GenWithIsBoot mod #

This data type just pairs a value mod with an IsBootInterface flag. In practice, mod is usually a Module or ModuleName'.

Constructors

GWIB 

Instances

Instances details
Foldable GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

fold :: Monoid m => GenWithIsBoot m -> m #

foldMap :: Monoid m => (a -> m) -> GenWithIsBoot a -> m #

foldMap' :: Monoid m => (a -> m) -> GenWithIsBoot a -> m #

foldr :: (a -> b -> b) -> b -> GenWithIsBoot a -> b #

foldr' :: (a -> b -> b) -> b -> GenWithIsBoot a -> b #

foldl :: (b -> a -> b) -> b -> GenWithIsBoot a -> b #

foldl' :: (b -> a -> b) -> b -> GenWithIsBoot a -> b #

foldr1 :: (a -> a -> a) -> GenWithIsBoot a -> a #

foldl1 :: (a -> a -> a) -> GenWithIsBoot a -> a #

toList :: GenWithIsBoot a -> [a] #

null :: GenWithIsBoot a -> Bool #

length :: GenWithIsBoot a -> Int #

elem :: Eq a => a -> GenWithIsBoot a -> Bool #

maximum :: Ord a => GenWithIsBoot a -> a #

minimum :: Ord a => GenWithIsBoot a -> a #

sum :: Num a => GenWithIsBoot a -> a #

product :: Num a => GenWithIsBoot a -> a #

Traversable GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

traverse :: Applicative f => (a -> f b) -> GenWithIsBoot a -> f (GenWithIsBoot b) #

sequenceA :: Applicative f => GenWithIsBoot (f a) -> f (GenWithIsBoot a) #

mapM :: Monad m => (a -> m b) -> GenWithIsBoot a -> m (GenWithIsBoot b) #

sequence :: Monad m => GenWithIsBoot (m a) -> m (GenWithIsBoot a) #

Functor GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> GenWithIsBoot a -> GenWithIsBoot b #

(<$) :: a -> GenWithIsBoot b -> GenWithIsBoot a #

Show mod => Show (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

Binary a => Binary (GenWithIsBoot a) 
Instance details

Defined in GHC.Unit.Types

Outputable a => Outputable (GenWithIsBoot a) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc #

Eq mod => Eq (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

(/=) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

Ord mod => Ord (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

data GenInstantiatedUnit unit #

An instantiated unit.

It identifies an indefinite library (with holes) that has been instantiated.

This unit may be indefinite or not (i.e. with remaining holes or not). If it is definite, we don't know if it has already been compiled and installed in a database. Nevertheless, we have a mechanism called "improvement" to try to match a fully instantiated unit with existing compiled and installed units: see Note [VirtUnit to RealUnit improvement].

An indefinite unit identifier pretty-prints to something like p[H=H,A=aimpl:A>] (p is the IndefUnitId, and the brackets enclose the module substitution).

Constructors

InstantiatedUnit 

Fields

newtype Definite unit #

A definite unit (i.e. without any free module hole)

Constructors

Definite 

Fields

Instances

Instances details
Functor Definite 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> Definite a -> Definite b #

(<$) :: a -> Definite b -> Definite a #

Uniquable unit => Uniquable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique #

IsUnitId unit => IsUnitId (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Definite unit -> FastString #

Binary unit => Binary (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Definite unit -> IO () #

put :: BinHandle -> Definite unit -> IO (Bin (Definite unit)) #

get :: BinHandle -> IO (Definite unit) #

Outputable unit => Outputable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc #

Eq unit => Eq (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: Definite unit -> Definite unit -> Bool #

(/=) :: Definite unit -> Definite unit -> Bool #

Ord unit => Ord (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Definite unit -> Definite unit -> Ordering #

(<) :: Definite unit -> Definite unit -> Bool #

(<=) :: Definite unit -> Definite unit -> Bool #

(>) :: Definite unit -> Definite unit -> Bool #

(>=) :: Definite unit -> Definite unit -> Bool #

max :: Definite unit -> Definite unit -> Definite unit #

min :: Definite unit -> Definite unit -> Definite unit #

type DefUnitId = Definite UnitId #

A DefUnitId is an UnitId with the invariant that it only refers to a definite library; i.e., one we have generated code for.

virtualUnitId :: InstantiatedUnit -> UnitId #

Return the virtual UnitId of an on-the-fly instantiated unit.

unitIsDefinite :: Unit -> Bool #

A Unit is definite if it has no free holes.

unitFreeModuleHoles :: GenUnit u -> UniqDSet ModuleName #

Retrieve the set of free module holes of a Unit.

stableUnitCmp :: Unit -> Unit -> Ordering #

Compares unit ids lexically, rather than by their Uniques

moduleFreeHoles :: GenModule (GenUnit u) -> UniqDSet ModuleName #

Calculate the free holes of a Module. If this set is non-empty, this module was defined in an indefinite library that had required signatures.

If a module has free holes, that means that substitutions can operate on it; if it has no free holes, substituting over a module has no effect.

mkVirtUnit :: IsUnitId u => Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u #

Smart constructor for instantiated GenUnit

mkInstantiatedUnitHash :: IsUnitId u => Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> FastString #

Generate a uniquely identifying hash (internal unit-id) for an instantiated unit.

This is a one-way function. If the indefinite unit has not been instantiated at all, we return its unit-id.

This hash is completely internal to GHC and is not used for symbol names or file paths. It is different from the hash Cabal would produce for the same instantiated unit.

mkInstantiatedUnit :: IsUnitId u => Indefinite u -> GenInstantiations u -> GenInstantiatedUnit u #

Create a new GenInstantiatedUnit given an explicit module substitution.

mapInstantiations :: IsUnitId v => (u -> v) -> GenInstantiations u -> GenInstantiations v #

Map over the unit identifier of unit instantiations.

mapGenUnit :: IsUnitId v => (u -> v) -> GenUnit u -> GenUnit v #

Map over the unit type of a GenUnit

mainUnitId :: UnitId #

This is the package Id for the current program. It is the default package Id if you don't specify a package name. We don't add this prefix to symbol names, since there can be only one main package per program.

fsToUnit :: FastString -> Unit #

Create a new simple unit identifier from a FastString. Internally, this is primarily used to specify wired-in unit identifiers.

stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering #

Compares module names lexically, rather than by their Uniques

moduleNameSlashes :: ModuleName -> String #

Returns the string version of the module name, with dots replaced by slashes.

moduleNameColons :: ModuleName -> String #

Returns the string version of the module name, with dots replaced by colons.

unitIdFS :: UnitId -> FastString #

The full hashed unit identifier, including the component id and the hash.

type Module = GenModule Unit #

A Module is a pair of a Unit and a ModuleName.

newtype Indefinite unit #

Constructors

Indefinite 

Fields

Instances

Instances details
Functor Indefinite 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> Indefinite a -> Indefinite b #

(<$) :: a -> Indefinite b -> Indefinite a #

Uniquable unit => Uniquable (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Indefinite unit -> Unique #

IsUnitId unit => IsUnitId (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Indefinite unit -> FastString #

Binary unit => Binary (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Indefinite unit -> IO () #

put :: BinHandle -> Indefinite unit -> IO (Bin (Indefinite unit)) #

get :: BinHandle -> IO (Indefinite unit) #

Outputable unit => Outputable (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Indefinite unit -> SDoc #

Eq unit => Eq (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: Indefinite unit -> Indefinite unit -> Bool #

(/=) :: Indefinite unit -> Indefinite unit -> Bool #

Ord unit => Ord (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Indefinite unit -> Indefinite unit -> Ordering #

(<) :: Indefinite unit -> Indefinite unit -> Bool #

(<=) :: Indefinite unit -> Indefinite unit -> Bool #

(>) :: Indefinite unit -> Indefinite unit -> Bool #

(>=) :: Indefinite unit -> Indefinite unit -> Bool #

max :: Indefinite unit -> Indefinite unit -> Indefinite unit #

min :: Indefinite unit -> Indefinite unit -> Indefinite unit #

type IndefUnitId = Indefinite UnitId #

An IndefUnitId is an UnitId with the invariant that it only refers to an indefinite library; i.e., one that can be instantiated.

data GenUnit uid #

A unit identifier identifies a (possibly partially) instantiated library. It is primarily used as part of Module, which in turn is used in Name, which is used to give names to entities when typechecking.

There are two possible forms for a Unit:

1) It can be a RealUnit, in which case we just have a DefUnitId that uniquely identifies some fully compiled, installed library we have on disk.

2) It can be an VirtUnit. When we are typechecking a library with missing holes, we may need to instantiate a library on the fly (in which case we don't have any on-disk representation.) In that case, you have an InstantiatedUnit, which explicitly records the instantiation, so that we can substitute over it.

Constructors

RealUnit !(Definite uid)

Installed definite unit (either a fully instantiated unit or a closed unit)

VirtUnit !(GenInstantiatedUnit uid)

Virtual unit instantiated on-the-fly. It may be definite if all the holes are instantiated but we don't have code objects for it.

HoleUnit

Fake hole unit

Instances

Instances details
Data Unit 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unit -> c Unit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unit #

toConstr :: Unit -> Constr #

dataTypeOf :: Unit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unit) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unit) #

gmapT :: (forall b. Data b => b -> b) -> Unit -> Unit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r #

gmapQ :: (forall d. Data d => d -> u) -> Unit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit -> m Unit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit #

Show Module Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Show Unit 
Instance details

Defined in GHC.Unit.Types

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

NFData Unit 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: Unit -> () #

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Binary Unit 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Unit -> IO () #

put :: BinHandle -> Unit -> IO (Bin Unit) #

get :: BinHandle -> IO Unit #

Outputable Module 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc #

Outputable Unit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc #

Ord Unit 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

IsUnitId u => Uniquable (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: GenUnit u -> Unique #

IsUnitId u => IsUnitId (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: GenUnit u -> FastString #

IsUnitId u => Eq (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenUnit u -> GenUnit u -> Bool #

(/=) :: GenUnit u -> GenUnit u -> Bool #

data GenModule unit #

A generic module is a pair of a unit identifier and a ModuleName.

Constructors

Module !unit !ModuleName 

Instances

Instances details
Functor GenModule 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> GenModule a -> GenModule b #

(<$) :: a -> GenModule b -> GenModule a #

Show Module Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Outputable InstalledModule 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstalledModule -> SDoc #

Outputable InstantiatedModule 
Instance details

Defined in GHC.Unit.Types

Outputable Module 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc #

Data unit => Data (GenModule unit) 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenModule unit -> c (GenModule unit) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenModule unit) #

toConstr :: GenModule unit -> Constr #

dataTypeOf :: GenModule unit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenModule unit)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GenModule unit)) #

gmapT :: (forall b. Data b => b -> b) -> GenModule unit -> GenModule unit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenModule unit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenModule unit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) #

NFData (GenModule a) 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: GenModule a -> () #

Binary a => Binary (GenModule a) 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> GenModule a -> IO () #

put :: BinHandle -> GenModule a -> IO (Bin (GenModule a)) #

get :: BinHandle -> IO (GenModule a) #

Eq unit => Eq (GenModule unit) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenModule unit -> GenModule unit -> Bool #

(/=) :: GenModule unit -> GenModule unit -> Bool #

Ord unit => Ord (GenModule unit) 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: GenModule unit -> GenModule unit -> Ordering #

(<) :: GenModule unit -> GenModule unit -> Bool #

(<=) :: GenModule unit -> GenModule unit -> Bool #

(>) :: GenModule unit -> GenModule unit -> Bool #

(>=) :: GenModule unit -> GenModule unit -> Bool #

max :: GenModule unit -> GenModule unit -> GenModule unit #

min :: GenModule unit -> GenModule unit -> GenModule unit #

data ModuleName #

A ModuleName is essentially a simple string, e.g. Data.List.

Instances

Instances details
Data ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName #

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) #

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

Show ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

NFData ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

rnf :: ModuleName -> () #

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Binary ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Outputable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc #

Eq ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Ord ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Hashable ModuleName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

ToHie (IEContext (LocatedA ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA ModuleName) -> HieM [HieAST Type]

type Anno ModuleName 
Instance details

Defined in GHC.Hs.ImpExp

Syntax re-exports

data HsModule #

Haskell Module

All we actually declare here is the top-level structure for a module.

Constructors

HsModule 

Fields

Instances

Instances details
Data HsModule 
Instance details

Defined in GHC.Hs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule -> c HsModule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsModule #

toConstr :: HsModule -> Constr #

dataTypeOf :: HsModule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsModule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsModule) #

gmapT :: (forall b. Data b => b -> b) -> HsModule -> HsModule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsModule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule #

NFData HsModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: HsModule -> () #

Outputable HsModule 
Instance details

Defined in GHC.Hs

Methods

ppr :: HsModule -> SDoc #

data SrcSpanAnn' a #

The 'SrcSpanAnn'' type wraps a normal SrcSpan, together with an extra annotation type. This is mapped to a specific GenLocated usage in the AST through the XRec and Anno type families.

Instances

Instances details
Functor SrcSpanAnn' Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

fmap :: (a -> b) -> SrcSpanAnn' a -> SrcSpanAnn' b #

(<$) :: a -> SrcSpanAnn' b -> SrcSpanAnn' a #

Data a => Data (SrcSpanAnn' a) 
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) -> SrcSpanAnn' a -> c (SrcSpanAnn' a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SrcSpanAnn' a) #

toConstr :: SrcSpanAnn' a -> Constr #

dataTypeOf :: SrcSpanAnn' a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SrcSpanAnn' a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SrcSpanAnn' a)) #

gmapT :: (forall b. Data b => b -> b) -> SrcSpanAnn' a -> SrcSpanAnn' a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpanAnn' a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpanAnn' a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcSpanAnn' a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpanAnn' a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

Semigroup an => Semigroup (SrcSpanAnn' an) 
Instance details

Defined in GHC.Parser.Annotation

NFData (SrcSpanAnn' a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: SrcSpanAnn' a -> () #

Binary a => Binary (LocatedL a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

put_ :: BinHandle -> LocatedL a -> IO () #

put :: BinHandle -> LocatedL a -> IO (Bin (LocatedL a)) #

get :: BinHandle -> IO (LocatedL a) #

Outputable a => Outputable (SrcSpanAnn' a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc #

Eq a => Eq (SrcSpanAnn' a) 
Instance details

Defined in GHC.Parser.Annotation

HasSrcSpan (SrcSpanAnn' ann) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

Methods

getLoc :: SrcSpanAnn' ann -> SrcSpan Source #

HasLoc (LocatedA a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedA a -> SrcSpan

HasLoc (LocatedN a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: LocatedN a -> SrcSpan

HiePass p => HasType (LocatedA (HsBind (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsBind (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (HsExpr (GhcPass p)))

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => HasType (LocatedA (Pat (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LocatedA (Pat (GhcPass p)) -> HieM [HieAST Type]

ToHie (LBooleanFormula (LocatedN Name)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (ImportDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ImportDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA HsWrapper) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA HsWrapper -> HieM [HieAST Type]

ToHie (LocatedA (FixitySig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FixitySig GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (AnnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (AnnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ClsInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ClsInstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ConDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DataFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (DefaultDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DefaultDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (DerivDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (DerivDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FamilyDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FamilyDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (ForeignDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ForeignDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (FunDep GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (FunDep GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (InstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (InstDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RoleAnnotDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (RuleDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (RuleDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (RuleDecls GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (SpliceDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (SpliceDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (StandaloneKindSig GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (TyClDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (TyClDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (TyFamInstDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedA (WarnDecl GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecl GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (WarnDecls GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (WarnDecls GhcRn) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsCmd (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsExpr (GhcPass p)) -> HieM [HieAST Type]

HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsSplice (GhcPass p)) -> HieM [HieAST Type]

(HiePass p, Data (body (GhcPass p)), AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

ToHie (LocatedA (ConDeclField GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (ConDeclField GhcRn) -> HieM [HieAST Type]

ToHie (LocatedA (HsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedA (HsType GhcRn) -> HieM [HieAST Type]

ToHie (LocatedC (DerivClauseTys GhcRn)) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedC [LocatedA (HsType GhcRn)]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedC [LocatedA (HsType GhcRn)] -> HieM [HieAST Type]

ToHie (LocatedL [LocatedA (ConDeclField GhcRn)]) 
Instance details

Defined in Compat.HieAst

ToHie (LocatedP OverlapMode) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LocatedP OverlapMode -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) -> HieM [HieAST Type]

HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LocatedA (HsBind (GhcPass p))) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedA a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedA a) -> HieM [HieAST Type]

ToHie (Context (Located a)) => ToHie (Context (LocatedN a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (LocatedN a) -> HieM [HieAST Type]

ToHie (EvBindContext (LocatedA TcEvBinds)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: EvBindContext (LocatedA TcEvBinds) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA (IE GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA (IE GhcRn)) -> HieM [HieAST Type]

ToHie (IEContext (LocatedA ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LocatedA ModuleName) -> HieM [HieAST Type]

HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (LocatedA (Pat (GhcPass p))) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data arg, Data label) => ToHie (RContext (LocatedA (HsRecField' label arg))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LocatedA (HsRecField' label arg)) -> HieM [HieAST Type]

HiePass p => ToHie (RScoped (LocatedA (IPBind (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (IPBind (GhcPass p))) -> HieM [HieAST Type]

(ToHie (LocatedA (body (GhcPass p))), AnnoBody p body, HiePass p) => ToHie (RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p)))))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LocatedA (Stmt (GhcPass p) (LocatedA (body (GhcPass p))))) -> HieM [HieAST Type]

HiePass p => ToHie (SigContext (LocatedA (Sig (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LocatedA (Sig (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LocatedA (HsSigType GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LocatedA (HsSigType GhcRn)) -> HieM [HieAST Type]

ToHie (TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (FamEqn GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsSigType GhcRn))) -> HieM [HieAST Type]

ToHie (TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (HsWildCardBndrs GhcRn (LocatedA (HsType GhcRn))) -> HieM [HieAST Type]

Data flag => ToHie (TVScoped (LocatedA (HsTyVarBndr flag GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LocatedA (HsTyVarBndr flag GhcRn)) -> HieM [HieAST Type]

NamedThing (Located a) => NamedThing (LocatedAn an a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc #

HasSrcSpan (GenLocated (SrcSpanAnn' ann) a) Source # 
Instance details

Defined in Development.IDE.GHC.Compat.Core

(ToHie (LocatedA (body (GhcPass p))), HiePass p, AnnoBody p body) => ToHie (GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

(HiePass p, AnnoBody p body, ToHie (LocatedA (body (GhcPass p)))) => ToHie (MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) -> HieM [HieAST Type]

type Anno (LocatedA (IE (GhcPass p))) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedA (IE (GhcPass p))] 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
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)))] 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (ConDeclField (GhcPass _1))] 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) 
Instance details

Defined in GHC.Hs.Pat

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) 
Instance details

Defined in GHC.Hs.Expr

module GHC.Parser

getOptionsFromFile #

Arguments

:: DynFlags 
-> FilePath

Input file

-> IO [Located String]

Parsed options, if any.

Parse OPTIONS and LANGUAGE pragmas of the source file.

Throws a SourceError if flag parsing fails (including unsupported flags.)

getOptions #

Arguments

:: DynFlags 
-> StringBuffer

Input Buffer

-> FilePath

Source filename. Used for location info.

-> [Located String]

Parsed options.

Parse OPTIONS and LANGUAGE pragmas of the source file.

Throws a SourceError if flag parsing fails (including unsupported flags.)

checkProcessArgsResult :: MonadIO m => [Located String] -> m () #

Complain about non-dynamic flags in OPTIONS pragmas.

Throws a SourceError if the input list is non-empty claiming that the input flags are unknown.

data Token #

Constructors

ITas 
ITcase 
ITclass 
ITdata 
ITdefault 
ITderiving 
ITdo (Maybe FastString) 
ITelse 
IThiding 
ITforeign 
ITif 
ITimport 
ITin 
ITinfix 
ITinfixl 
ITinfixr 
ITinstance 
ITlet 
ITmodule 
ITnewtype 
ITof 
ITqualified 
ITthen 
ITtype 
ITwhere 
ITforall IsUnicodeSyntax 
ITexport 
ITlabel 
ITdynamic 
ITsafe 
ITinterruptible 
ITunsafe 
ITstdcallconv 
ITccallconv 
ITcapiconv 
ITprimcallconv 
ITjavascriptcallconv 
ITmdo (Maybe FastString) 
ITfamily 
ITrole 
ITgroup 
ITby 
ITusing 
ITpattern 
ITstatic 
ITstock 
ITanyclass 
ITvia 
ITunit 
ITsignature 
ITdependency 
ITrequires 
ITinline_prag SourceText InlineSpec RuleMatchInfo 
ITspec_prag SourceText 
ITspec_inline_prag SourceText Bool 
ITsource_prag SourceText 
ITrules_prag SourceText 
ITwarning_prag SourceText 
ITdeprecated_prag SourceText 
ITline_prag SourceText 
ITcolumn_prag SourceText 
ITscc_prag SourceText 
ITunpack_prag SourceText 
ITnounpack_prag SourceText 
ITann_prag SourceText 
ITcomplete_prag SourceText 
ITclose_prag 
IToptions_prag String 
ITinclude_prag String 
ITlanguage_prag 
ITminimal_prag SourceText 
IToverlappable_prag SourceText 
IToverlapping_prag SourceText 
IToverlaps_prag SourceText 
ITincoherent_prag SourceText 
ITctype SourceText 
ITcomment_line_prag 
ITdotdot 
ITcolon 
ITdcolon IsUnicodeSyntax 
ITequal 
ITlam 
ITlcase 
ITvbar 
ITlarrow IsUnicodeSyntax 
ITrarrow IsUnicodeSyntax 
ITdarrow IsUnicodeSyntax 
ITlolly 
ITminus 
ITprefixminus 
ITbang 
ITtilde 
ITat 
ITtypeApp 
ITpercent 
ITstar IsUnicodeSyntax 
ITdot 
ITproj Bool 
ITbiglam 
ITocurly 
ITccurly 
ITvocurly 
ITvccurly 
ITobrack 
ITopabrack 
ITcpabrack 
ITcbrack 
IToparen 
ITcparen 
IToubxparen 
ITcubxparen 
ITsemi 
ITcomma 
ITunderscore 
ITbackquote 
ITsimpleQuote 
ITvarid FastString 
ITconid FastString 
ITvarsym FastString 
ITconsym FastString 
ITqvarid (FastString, FastString) 
ITqconid (FastString, FastString) 
ITqvarsym (FastString, FastString) 
ITqconsym (FastString, FastString) 
ITdupipvarid FastString 
ITlabelvarid FastString 
ITchar SourceText Char 
ITstring SourceText FastString 
ITinteger IntegralLit 
ITrational FractionalLit 
ITprimchar SourceText Char 
ITprimstring SourceText ByteString 
ITprimint SourceText Integer 
ITprimword SourceText Integer 
ITprimfloat FractionalLit 
ITprimdouble FractionalLit 
ITopenExpQuote HasE IsUnicodeSyntax 
ITopenPatQuote 
ITopenDecQuote 
ITopenTypQuote 
ITcloseQuote IsUnicodeSyntax 
ITopenTExpQuote HasE 
ITcloseTExpQuote 
ITdollar 
ITdollardollar 
ITtyQuote 
ITquasiQuote (FastString, FastString, PsSpan) 
ITqQuasiQuote (FastString, FastString, FastString, PsSpan) 
ITproc 
ITrec 
IToparenbar IsUnicodeSyntax
(|
ITcparenbar IsUnicodeSyntax
|)
ITlarrowtail IsUnicodeSyntax
-<
ITrarrowtail IsUnicodeSyntax
>-
ITLarrowtail IsUnicodeSyntax
-<<
ITRarrowtail IsUnicodeSyntax
>>-
ITunknown String

Used when the lexer can't make sense of it

ITeof

end of file token

ITdocCommentNext String PsSpan

something beginning -- |

ITdocCommentPrev String PsSpan

something beginning -- ^

ITdocCommentNamed String PsSpan

something beginning -- $

ITdocSection Int String PsSpan

a section heading

ITdocOptions String PsSpan

doc options (prune, ignore-exports, etc)

ITlineComment String PsSpan

comment starting by "--"

ITblockComment String PsSpan

comment in {- -}

Instances

Instances details
Show Token 
Instance details

Defined in GHC.Parser.Lexer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Outputable Token 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc #

data ParserOpts #

Parser options.

See mkParserOpts to construct this.

Constructors

ParserOpts 

Fields

data ParseResult a #

The result of running a parser.

Constructors

POk

The parser has consumed a (possibly empty) prefix of the input and produced a result. Use getMessages to check for accumulated warnings and non-fatal errors.

Fields

  • PState

    The resulting parsing state. Can be used to resume parsing.

  • a

    The resulting value.

PFailed

The parser has consumed a (possibly empty) prefix of the input and failed.

Fields

newtype P a #

The parsing monad, isomorphic to StateT PState Maybe.

Constructors

P 

Fields

Instances

Instances details
Applicative P 
Instance details

Defined in GHC.Parser.Lexer

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Functor P 
Instance details

Defined in GHC.Parser.Lexer

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Monad P 
Instance details

Defined in GHC.Parser.Lexer

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

MonadP P 
Instance details

Defined in GHC.Parser.Lexer

class Monad m => MonadP (m :: Type -> Type) where #

An mtl-style class for monads that support parsing-related operations. For example, sometimes we make a second pass over the parsing results to validate, disambiguate, or rearrange them, and we do so in the PV monad which cannot consume input but can report parsing errors, check for extension bits, and accumulate parsing annotations. Both P and PV are instances of MonadP.

MonadP grants us convenient overloading. The other option is to have separate operations for each monad: addErrorP vs addErrorPV, getBitP vs getBitPV, and so on.

Methods

addError :: PsError -> m () #

Add a non-fatal error. Use this when the parser can produce a result despite the error.

For example, when GHC encounters a forall in a type, but -XExplicitForAll is disabled, the parser constructs ForAllTy as if -XExplicitForAll was enabled, adding a non-fatal error to the accumulator.

Control flow wise, non-fatal errors act like warnings: they are added to the accumulator and parsing continues. This allows GHC to report more than one parse error per file.

addWarning :: WarningFlag -> PsWarning -> m () #

Add a warning to the accumulator. Use getMessages to get the accumulated warnings.

addFatalError :: PsError -> m a #

Add a fatal error. This will be the last error reported by the parser, and the parser will not produce any result, ending in a PFailed state.

getBit :: ExtBits -> m Bool #

Check if a given flag is currently set in the bitmap.

allocateCommentsP :: RealSrcSpan -> m EpAnnComments #

Go through the comment_q in PState and remove all comments that belong within the given span

allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments #

Go through the comment_q in PState and remove all comments that come before or within the given span

allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments #

Go through the comment_q in PState and remove all comments that come after the given span

data HdkComment #

Haddock comment as produced by the lexer. These are accumulated in PState and then processed in GHC.Parser.PostProcess.Haddock.

Instances

Instances details
Show HdkComment 
Instance details

Defined in GHC.Parser.Lexer

data ExtBits #

Various boolean flags, mostly language extensions, that impact lexing and parsing. Note that a handful of these can change during lexing/parsing.

Instances

Instances details
Enum ExtBits 
Instance details

Defined in GHC.Parser.Lexer

xunset :: ExtBits -> ExtsBitmap -> ExtsBitmap #

xtest :: ExtBits -> ExtsBitmap -> Bool #

xset :: ExtBits -> ExtsBitmap -> ExtsBitmap #

warnopt :: WarningFlag -> ParserOpts -> Bool #

Test whether a WarningFlag is set

setLastToken :: PsSpan -> Int -> P () #

pushLexState :: Int -> P () #

popContext :: P () #

mkParserOpts #

Arguments

:: EnumSet WarningFlag

warnings flags enabled

-> EnumSet Extension

permitted language extensions enabled

-> Bool

are safe imports on?

-> Bool

keeping Haddock comment tokens

-> Bool

keep regular comment tokens

-> Bool

If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update the internal position kept by the parser. Otherwise, those pragmas are lexed as ITline_prag and ITcolumn_prag tokens.

-> ParserOpts 

Given exactly the information needed, set up the ParserOpts

mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn) #

Given a SrcSpan that surrounds a HsPar or HsParTy, generate AddEpAnn values for the opening and closing bordering on the start and end of the span

lexerDbg :: Bool -> (Located Token -> P a) -> P a #

lexer :: Bool -> (Located Token -> P a) -> P a #

initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState #

Set parser options for parsing OPTIONS pragmas

getMessages :: PState -> (Bag PsWarning, Bag PsError) #

Get the warnings and errors accumulated so far. Does not take -Werror into account.

getErrorMessages :: PState -> Bag PsError #

Get a bag of the errors that have been accumulated so far. Does not take -Werror into account.

failMsgP :: (SrcSpan -> PsError) -> P a #

pattern HsFieldBind :: XHsRecField id -> id -> arg -> Bool -> HsRecField' id arg Source #

hfbLHS :: HsRecField' id arg -> id Source #

hfbRHS :: HsRecField' id arg -> arg Source #

data Extension #

The language extensions known to GHC.

Note that there is an orphan Binary instance for this type supplied by the GHC.LanguageExtensions module provided by ghc-boot. We can't provide here as this would require adding transitive dependencies to the template-haskell package, which must have a minimal dependency set.

Constructors

OverlappingInstances 
UndecidableInstances 
IncoherentInstances 
UndecidableSuperClasses 
MonomorphismRestriction 
MonoLocalBinds 
DeepSubsumption 
RelaxedPolyRec 
ExtendedDefaultRules 
ForeignFunctionInterface 
UnliftedFFITypes 
InterruptibleFFI 
CApiFFI 
GHCForeignImportPrim 
JavaScriptFFI 
ParallelArrays 
Arrows 
TemplateHaskell 
TemplateHaskellQuotes 
QualifiedDo 
QuasiQuotes 
ImplicitParams 
ImplicitPrelude 
ScopedTypeVariables 
AllowAmbiguousTypes 
UnboxedTuples 
UnboxedSums 
UnliftedNewtypes 
UnliftedDatatypes 
BangPatterns 
TypeFamilies 
TypeFamilyDependencies 
TypeInType 
OverloadedStrings 
OverloadedLists 
NumDecimals 
DisambiguateRecordFields 
RecordWildCards 
RecordPuns 
ViewPatterns 
GADTs 
GADTSyntax 
NPlusKPatterns 
DoAndIfThenElse 
BlockArguments 
RebindableSyntax 
ConstraintKinds 
PolyKinds 
DataKinds 
InstanceSigs 
ApplicativeDo 
LinearTypes 
StandaloneDeriving 
DeriveDataTypeable 
AutoDeriveTypeable 
DeriveFunctor 
DeriveTraversable 
DeriveFoldable 
DeriveGeneric 
DefaultSignatures 
DeriveAnyClass 
DeriveLift 
DerivingStrategies 
DerivingVia 
TypeSynonymInstances 
FlexibleContexts 
FlexibleInstances 
ConstrainedClassMethods 
MultiParamTypeClasses 
NullaryTypeClasses 
FunctionalDependencies 
UnicodeSyntax 
ExistentialQuantification 
MagicHash 
EmptyDataDecls 
KindSignatures 
RoleAnnotations 
ParallelListComp 
TransformListComp 
MonadComprehensions 
GeneralizedNewtypeDeriving 
RecursiveDo 
PostfixOperators 
TupleSections 
PatternGuards 
LiberalTypeSynonyms 
RankNTypes 
ImpredicativeTypes 
TypeOperators 
ExplicitNamespaces 
PackageImports 
ExplicitForAll 
AlternativeLayoutRule 
AlternativeLayoutRuleTransitional 
DatatypeContexts 
NondecreasingIndentation 
RelaxedLayout 
TraditionalRecordSyntax 
LambdaCase 
MultiWayIf 
BinaryLiterals 
NegativeLiterals 
HexFloatLiterals 
DuplicateRecordFields 
OverloadedLabels 
EmptyCase 
PatternSynonyms 
PartialTypeSignatures 
NamedWildCards 
StaticPointers 
TypeApplications 
Strict 
StrictData 
EmptyDataDeriving 
NumericUnderscores 
QuantifiedConstraints 
StarIsType 
ImportQualifiedPost 
CUSKs 
StandaloneKindSignatures 
LexicalNegation 
FieldSelectors 
OverloadedRecordDot 
OverloadedRecordUpdate 

Bundled Patterns

pattern NamedFieldPuns :: Extension 

Instances

Instances details
Bounded Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Enum Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Show Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Outputable Extension 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Extension -> SDoc #

Eq Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Ord Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

type Rep Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

type Rep Extension = D1 ('MetaData "Extension" "GHC.LanguageExtensions.Type" "ghc-boot-th-9.2.4" 'False) ((((((C1 ('MetaCons "Cpp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordPuns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type))))))))

field_label :: a -> a Source #