apply-refact-0.12.0.0: Perform refactorings specified by the refact library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Refact.Compat

Synopsis

ApiAnnotation / GHC.Parser.ApiAnnotation

data AnnKeywordId #

Exact print annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not otherwise captured in the AST.

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

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

Constructors

AnnAnyclass 
AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseB

'|)'

AnnCloseBU

'|)', unicode variant

AnnCloseC

'}'

AnnCloseQ

'|]'

AnnCloseQU

'|]', unicode variant

AnnCloseP

')'

AnnClosePH

'#)'

AnnCloseS

']'

AnnColon 
AnnComma

as a list separator

AnnCommaTuple

in a RdrName for a tuple

AnnDarrow

'=>'

AnnDarrowU

'=>', unicode variant

AnnData 
AnnDcolon

'::'

AnnDcolonU

'::', unicode variant

AnnDefault 
AnnDeriving 
AnnDo 
AnnDot

.

AnnDotdot

'..'

AnnElse 
AnnEqual 
AnnExport 
AnnFamily 
AnnForall 
AnnForallU

Unicode variant

AnnForeign 
AnnFunId

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

AnnGroup 
AnnHeader

for CType

AnnHiding 
AnnIf 
AnnImport 
AnnIn 
AnnInfix

'infix' or 'infixl' or 'infixr'

AnnInstance 
AnnLam 
AnnLarrow

'<-'

AnnLarrowU

'<-', unicode variant

AnnLet 
AnnLollyU

The unicode arrow

AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnName

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

AnnOf 
AnnOpen

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

AnnOpenB

'(|'

AnnOpenBU

'(|', unicode variant

AnnOpenC

'{'

AnnOpenE

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

AnnOpenEQ

'[|'

AnnOpenEQU

'[|', unicode variant

AnnOpenP

'('

AnnOpenS

'['

AnnOpenPH

'(#'

AnnDollar

prefix $ -- TemplateHaskell

AnnDollarDollar

prefix $$ -- TemplateHaskell

AnnPackageName 
AnnPattern 
AnnPercent

% -- for HsExplicitMult

AnnPercentOne

'%1' -- for HsLinearArrow

AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThTyQuote

double '''

AnnTilde

~

AnnType 
AnnUnit

() for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnVia

via

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

->

AnnrarrowtailU

->, unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

Instances

Instances details
Data AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnKeywordId -> Constr #

dataTypeOf :: AnnKeywordId -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnKeywordId -> SDoc #

Eq AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Ord AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

data DeltaPos #

Spacing between output items when exact printing. It captures the spacing from the current print position on the page to the position required for the thing about to be printed. This is either on the same line in which case is is simply the number of spaces to emit, or it is some number of lines down, with a given column offset. The exact printing algorithm keeps track of the column offset pertaining to the current anchor position, so the deltaColumn is the additional spaces to add in this case. See https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations for details.

Constructors

SameLine 

Fields

DifferentLine 

Fields

Instances

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

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

toConstr :: DeltaPos -> Constr #

dataTypeOf :: DeltaPos -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Outputable DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc #

Eq DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Ord DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

BasicTypes / GHC.Types.Basic

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 #

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

ExactPrint (SourceText, RuleName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

DynFlags / GHC.Driver.Session

data FlagSpec flag #

Constructors

FlagSpec 

Fields

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 

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.

xFlags :: [FlagSpec Extension] #

These -Xblah flags can all be reversed with -XNoblah

ErrUtils

FastString / GHC.Data.FastString

data FastString #

A FastString is a UTF-8 encoded string together with a unique ID. All FastStrings are stored in a global hashtable to support fast O(1) comparison.

It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.

Instances

Instances details
Data FastString 
Instance details

Defined in GHC.Data.FastString

Methods

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

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

toConstr :: FastString -> Constr #

dataTypeOf :: FastString -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString FastString 
Instance details

Defined in GHC.Data.FastString

Monoid FastString 
Instance details

Defined in GHC.Data.FastString

Semigroup FastString 
Instance details

Defined in GHC.Data.FastString

Show FastString 
Instance details

Defined in GHC.Data.FastString

NFData FastString 
Instance details

Defined in GHC.Data.FastString

Methods

rnf :: FastString -> () #

Outputable FastString 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc #

ExactPrint FastString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Eq FastString 
Instance details

Defined in GHC.Data.FastString

ExactPrint (SourceText, RuleName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

mkFastString :: String -> FastString #

Creates a UTF-8 encoded FastString from a String

HeaderInfo / GHC.Parser.Header

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

HsExpr / GHC.Hs.Expr

data GRHS p body #

Guarded Right Hand Side.

Constructors

GRHS (XCGRHS p body) [GuardLStmt p] body 
XGRHS !(XXGRHS p body) 

Instances

Instances details
ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsExpr GhcPs -> Entry #

setAnnotationAnchor :: HsExpr GhcPs -> Anchor -> EpAnnComments -> HsExpr GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsExpr GhcPs -> EP w m (HsExpr GhcPs) #

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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

data Match p body #

Constructors

Match 

Fields

XMatch !(XXMatch p body) 

Instances

Instances details
ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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
ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

HsSyn / GHC.Hs

data HsParsedModule #

Constructors

HsParsedModule 

Fields

  • hpm_module :: Located HsModule
     
  • hpm_src_files :: [FilePath]

    extra source files (e.g. from #includes). The lexer collects these from '# file line' pragmas, which the C preprocessor leaves behind. These files and their timestamps are stored in the .hi file, so that we can force recompilation if any of them change (#3589)

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 #

Outputable HsModule 
Instance details

Defined in GHC.Hs

Methods

ppr :: HsModule -> SDoc #

ExactPrint HsModule

'Located (HsModule GhcPs)' corresponds to ParsedSource

Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsModule -> Entry #

setAnnotationAnchor :: HsModule -> Anchor -> EpAnnComments -> HsModule #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsModule -> EP w m HsModule #

HasDecls ParsedSource 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource #

data AnnsModule #

Constructors

AnnsModule 

Fields

Instances

Instances details
Data AnnsModule 
Instance details

Defined in GHC.Hs

Methods

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

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

toConstr :: AnnsModule -> Constr #

dataTypeOf :: AnnsModule -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq AnnsModule 
Instance details

Defined in GHC.Hs

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

data SyntaxExprTc #

An expression with wrappers, used for rebindable syntax

This should desugar to

syn_res_wrap $ syn_expr (syn_arg_wraps[0] arg0)
                        (syn_arg_wraps[1] arg1) ...

where the actual arguments come from elsewhere in the AST.

Instances

Instances details
Outputable SyntaxExprTc 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: SyntaxExprTc -> SDoc #

data SyntaxExprRn #

The function to use in rebindable syntax. See Note [NoSyntaxExpr].

Instances

Instances details
Outputable SyntaxExprRn 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: SyntaxExprRn -> SDoc #

type family SyntaxExprGhc (p :: Pass) = (r :: Type) | r -> p where ... #

data RecordUpdTc #

Extra data fields for a RecordUpd, added by the type checker

type PostTcTable = [(Name, PostTcExpr)] #

Post-Type checking Table

We use a PostTcTable where there are a bunch of pieces of evidence, more than is convenient to keep individually.

type PostTcExpr = HsExpr GhcTc #

Post-Type checking Expression

PostTcExpr is an evidence expression attached to the syntax tree by the type checker (c.f. postTcType).

data PendingTcSplice #

Pending Type-checker Splice

Instances

Instances details
Outputable PendingTcSplice 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: PendingTcSplice -> SDoc #

data PendingRnSplice #

Pending Renamer Splice

Instances

Instances details
Outputable PendingRnSplice 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: PendingRnSplice -> SDoc #

data HsWrap (hs_syn :: Type -> Type) #

HsWrap appears only in typechecker output Invariant: The contained Expr is *NOT* itself an HsWrap. See Note [Detecting forced eta expansion] in GHC.HsToCore.Expr. This invariant is maintained by mkHsWrap. hs_syn is something like HsExpr or HsCmd

Constructors

HsWrap HsWrapper (hs_syn GhcTc) 

Instances

Instances details
(Data (hs_syn GhcTc), Typeable hs_syn) => Data (HsWrap hs_syn) 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: HsWrap hs_syn -> Constr #

dataTypeOf :: HsWrap hs_syn -> DataType #

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

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

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

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

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

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

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

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

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

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

newtype HsSplicedT #

Instances

Instances details
Data HsSplicedT 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: HsSplicedT -> Constr #

dataTypeOf :: HsSplicedT -> DataType #

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

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

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

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

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

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

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

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

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

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

data HsExpansion a b #

Constructors

HsExpanded a b 

Instances

Instances details
(Data a, Data b) => Data (HsExpansion a b) 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsExpansion a b -> c (HsExpansion a b) #

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

toConstr :: HsExpansion a b -> Constr #

dataTypeOf :: HsExpansion a b -> DataType #

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsExpansion a b -> HsExpansion a b #

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

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

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpansion a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpansion a b -> m (HsExpansion a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpansion a b -> m (HsExpansion a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpansion a b -> m (HsExpansion a b) #

(Outputable a, Outputable b) => Outputable (HsExpansion a b)

Just print the original expression (the a).

Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsExpansion a b -> SDoc #

data GrhsAnn #

Constructors

GrhsAnn 

Fields

Instances

Instances details
Data GrhsAnn 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: GrhsAnn -> Constr #

dataTypeOf :: GrhsAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable GrhsAnn 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: GrhsAnn -> SDoc #

data EpAnnUnboundVar #

Instances

Instances details
Data EpAnnUnboundVar 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: EpAnnUnboundVar -> Constr #

dataTypeOf :: EpAnnUnboundVar -> DataType #

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

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

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

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

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

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

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

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

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

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

data EpAnnHsCase #

Instances

Instances details
Data EpAnnHsCase 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: EpAnnHsCase -> Constr #

dataTypeOf :: EpAnnHsCase -> DataType #

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

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

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

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

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

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

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

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

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

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

data DelayedSplice #

Instances

Instances details
Data DelayedSplice 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: DelayedSplice -> Constr #

dataTypeOf :: DelayedSplice -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnsLet #

Constructors

AnnsLet 

Instances

Instances details
Data AnnsLet 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: AnnsLet -> Constr #

dataTypeOf :: AnnsLet -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnsIf #

Instances

Instances details
Data AnnsIf 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: AnnsIf -> Constr #

dataTypeOf :: AnnsIf -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnProjection #

Constructors

AnnProjection 

Instances

Instances details
Data AnnProjection 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: AnnProjection -> Constr #

dataTypeOf :: AnnProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnFieldLabel #

Constructors

AnnFieldLabel 

Instances

Instances details
Data AnnFieldLabel 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: AnnFieldLabel -> Constr #

dataTypeOf :: AnnFieldLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

data AnnExplicitSum #

Instances

Instances details
Data AnnExplicitSum 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

toConstr :: AnnExplicitSum -> Constr #

dataTypeOf :: AnnExplicitSum -> DataType #

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

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

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

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

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

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

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

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

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

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

tupArgPresent :: forall (p :: Pass). HsTupArg (GhcPass p) -> Bool #

stripParensLHsExpr :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #

stripParensHsExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> HsExpr (GhcPass p) #

ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> IdP (GhcPass p) -> LHsExpr (GhcPass p) -> SDoc -> SDoc #

ppr_lexpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc #

ppr_lcmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc #

ppr_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc #

ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc #

ppr_cmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc #

ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc #

pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc #

pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc #

pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA) => HsStmtContext (GhcPass idL) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #

pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #

pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc #

pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #

pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc #

pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #

pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc #

pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc #

pprLCmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc #

pprHsBracket :: forall (p :: Pass). OutputableBndrId p => HsBracket (GhcPass p) -> SDoc #

pprGRHSs :: forall (idR :: Pass) body passL. (OutputableBndrId idR, Outputable body) => HsMatchContext passL -> GRHSs (GhcPass idR) body -> SDoc #

pprGRHS :: forall (idR :: Pass) body passL. (OutputableBndrId idR, Outputable body) => HsMatchContext passL -> GRHS (GhcPass idR) body -> SDoc #

pprDo :: forall (p :: Pass) body any. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => HsStmtContext any -> [LStmt (GhcPass p) body] -> SDoc #

pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc #

pprCmdArg :: forall (p :: Pass). OutputableBndrId p => HsCmdTop (GhcPass p) -> SDoc #

pprCmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc #

pprBy :: Outputable body => Maybe body -> SDoc #

pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #

pprBindStmt :: (Outputable pat, Outputable expr) => pat -> expr -> SDoc #

pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc #

pp_rhs :: Outputable body => HsMatchContext passL -> body -> SDoc #

parenthesizeHsExpr :: forall (p :: Pass). IsPass p => PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #

parenthesizeHsExpr p e checks if hsExprNeedsParens p e is true, and if so, surrounds e with an HsPar. Otherwise, it simply returns e.

noSyntaxExpr :: forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p) #

noExpr :: forall (p :: Pass). HsExpr (GhcPass p) #

This is used for rebindable-syntax pieces that are too polymorphic for tcSyntaxOp (trS_fmap and the mzip in ParStmt)

mkSyntaxExpr :: HsExpr GhcRn -> SyntaxExprRn #

Make a 'SyntaxExpr GhcRn' from an expression Used only in getMonadFailOp. See Note [Monad fail : Rebindable syntax, overloaded strings] in GHC.Rename.Expr

mkRnSyntaxExpr :: Name -> SyntaxExprRn #

Make a SyntaxExpr from a Name (the "rn" is because this is used in the renamer).

matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity #

isSingletonMatchGroup :: forall (p :: Pass) body. [LMatch (GhcPass p) body] -> Bool #

Is there only one RHS in this list of matches?

isEmptyMatchGroup :: forall (p :: Pass) body. MatchGroup (GhcPass p) body -> Bool #

isAtomicHsExpr :: forall (p :: Pass). IsPass p => HsExpr (GhcPass p) -> Bool #

hsLMatchPats :: forall (id :: Pass) body. LMatch (GhcPass id) body -> [LPat (GhcPass id)] #

hsExprNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> HsExpr (GhcPass p) -> Bool #

hsExprNeedsParens p e returns True if the expression e needs parentheses under precedence p.

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

Instances

Instances details
Data EpAnnSumPat 
Instance details

Defined in GHC.Hs.Pat

Methods

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

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

toConstr :: EpAnnSumPat -> Constr #

dataTypeOf :: EpAnnSumPat -> DataType #

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

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

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

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

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

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

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

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

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

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

data ConPatTc #

This is the extension field for ConPat, added after typechecking It adds quite a few extra fields, to support elaboration of pattern matching.

Constructors

ConPatTc 

Fields

  • cpt_arg_tys :: [Type]

    The universal arg types 1-1 with the universal tyvars of the constructor/pattern synonym Use (conLikeResTy pat_con cpt_arg_tys) to get the type of the pattern

  • cpt_tvs :: [TyVar]

    Existentially bound type variables in correctly-scoped order e.g. [k:* x:k]

  • cpt_dicts :: [EvVar]

    Ditto *coercion variables* and *dictionaries* One reason for putting coercion variable here I think is to ensure their kinds are zonked

  • cpt_binds :: TcEvBinds

    Bindings involving those dictionaries

  • cpt_wrap :: HsWrapper
     

data CoPat #

Coercion Pattern (translation only)

During desugaring a (CoPat co pat) turns into a cast with co on the scrutinee, followed by a match on pat.

Constructors

CoPat 

Fields

pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc #

patNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> Pat (GhcPass p) -> Bool #

patNeedsParens p pat returns True if the pattern pat needs parentheses under precedence p.

parenthesizePat :: forall (p :: Pass). IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) #

parenthesizePat p pat checks if patNeedsParens p pat is true, and if so, surrounds pat with a ParPat. Otherwise, it simply returns pat.

looksLazyPatBind :: forall (p :: Pass). HsBind (GhcPass p) -> Bool #

isSimplePat :: forall (x :: Pass). LPat (GhcPass x) -> Maybe (IdP (GhcPass x)) #

Is the pattern any of combination of:

  • (pat)
  • pat :: Type
  • ~pat
  • !pat
  • x (variable)

isBangedLPat :: forall (p :: Pass). LPat (GhcPass p) -> Bool #

data NHsValBindsLR idL #

Constructors

NValBinds [(RecFlag, LHsBinds idL)] [LSig GhcRn] 

data AnnSig #

Constructors

AnnSig 

Fields

Instances

Instances details
Data AnnSig 
Instance details

Defined in GHC.Hs.Binds

Methods

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

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

toConstr :: AnnSig -> Constr #

dataTypeOf :: AnnSig -> DataType #

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

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

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

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

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

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

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

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

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

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

pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc #

Using SourceText in case the pragma was spelled differently or used mixed case

ppr_sig :: forall (p :: Pass). OutputableBndrId p => Sig (GhcPass p) -> SDoc #

ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc #

pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc #

pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc] #

pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #

isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool #

isEmptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR -> Bool #

isEmptyIPBindsPR :: forall (p :: Pass). HsIPBinds (GhcPass p) -> Bool #

emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #

emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #

emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) #

emptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR #

class OutputableBndrFlag flag (p :: Pass) #

Minimal complete definition

pprTyVarBndr

Instances

Instances details
OutputableBndrFlag Specificity p 
Instance details

Defined in GHC.Hs.Type

OutputableBndrFlag () p 
Instance details

Defined in GHC.Hs.Type

Methods

pprTyVarBndr :: HsTyVarBndr () (GhcPass p) -> SDoc

type EpAnnForallTy #

Arguments

 = EpAnn (AddEpAnn, AddEpAnn)

Location of forall and -> for HsForAllVis Location of forall and . for HsForAllInvis

splitLHsSigmaTyInvis :: forall (p :: Pass). LHsType (GhcPass p) -> ([LHsTyVarBndr Specificity (GhcPass p)], Maybe (LHsContext (GhcPass p)), LHsType (GhcPass p)) #

Decompose a sigma type (of the form forall tvs. context => body) into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsQualTy :: forall (pass :: Pass). LHsType (GhcPass pass) -> (Maybe (LHsContext (GhcPass pass)), LHsType (GhcPass pass)) #

Decompose a type of the form context => body into its constituent parts.

Note that this function looks through parentheses, so it will work on types such as (context => ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsPatSynTy :: forall (p :: Pass). LHsSigType (GhcPass p) -> ([LHsTyVarBndr Specificity (GhcPass (NoGhcTcPass p))], Maybe (LHsContext (GhcPass p)), [LHsTyVarBndr Specificity (GhcPass p)], Maybe (LHsContext (GhcPass p)), LHsType (GhcPass p)) #

Decompose a pattern synonym type signature into its constituent parts.

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], Maybe (LHsContext GhcRn), LHsType GhcRn) #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into its constituent parts. Note that the [Name]s returned correspond to either:

  • The implicitly bound type variables (if the type lacks an outermost forall), or
  • The explicitly bound type variables (if the type has an outermost forall).

This function is careful not to look through parentheses. See Note [No nested foralls or contexts in instance types] for why this is important.

splitLHsGadtTy :: LHsSigType GhcPs -> (HsOuterSigTyVarBndrs GhcPs, Maybe (LHsContext GhcPs), LHsType GhcPs) #

Decompose a GADT type into its constituent parts. Returns (outer_bndrs, mb_ctxt, body), where:

  • outer_bndrs are HsOuterExplicit if the type has explicit, outermost type variable binders. Otherwise, they are HsOuterImplicit.
  • mb_ctxt is Just the context, if it is provided. Otherwise, it is Nothing.
  • body is the body of the type after the optional foralls and context.

This function is careful not to look through parentheses. See Note [GADT abstract syntax] (Wrinkle: No nested foralls or contexts) GHC.Hs.Decls for why this is important.

splitLHsForAllTyInvis_KP :: forall (pass :: Pass). LHsType (GhcPass pass) -> (Maybe (EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass)) #

Decompose a type of the form forall tvs. body into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Unlike splitLHsForAllTyInvis, this function does not look through parentheses, hence the suffix _KP (short for "Keep Parentheses").

splitLHsForAllTyInvis :: forall (pass :: Pass). LHsType (GhcPass pass) -> ((EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass)) #

Decompose a type of the form forall tvs. body into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them. Unlike splitLHsSigmaTyInvis, this function does not look through parentheses, hence the suffix _KP (short for "Keep Parentheses").

setHsTyVarBndrFlag :: forall flag flag' (pass :: Pass). flag -> HsTyVarBndr flag' (GhcPass pass) -> HsTyVarBndr flag (GhcPass pass) #

Set the attached flag

pprHsType :: forall (p :: Pass). OutputableBndrId p => HsType (GhcPass p) -> SDoc #

pprHsOuterSigTyVarBndrs :: forall (p :: Pass). OutputableBndrId p => HsOuterSigTyVarBndrs (GhcPass p) -> SDoc #

Prints the outermost forall in a type signature if one is written. If there is no outermost forall, nothing is printed.

pprHsOuterFamEqnTyVarBndrs :: forall (p :: Pass). OutputableBndrId p => HsOuterFamEqnTyVarBndrs (GhcPass p) -> SDoc #

Prints the explicit forall in a type family equation if one is written. If there is no explicit forall, nothing is printed.

pprHsForAll :: forall (p :: Pass). OutputableBndrId p => HsForAllTelescope (GhcPass p) -> Maybe (LHsContext (GhcPass p)) -> SDoc #

Prints a forall; When passed an empty list, prints forall ./forall -> only when -dppr-debug is enabled.

parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

parenthesizeHsType p ty checks if hsTypeNeedsParens p ty is true, and if so, surrounds ty with an HsParTy. Otherwise, it simply returns ty.

parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p) #

parenthesizeHsContext p ctxt checks if ctxt is a single constraint c such that hsTypeNeedsParens p c is true, and if so, surrounds c with an HsParTy to form a parenthesized ctxt. Otherwise, it simply returns ctxt unchanged.

mkHsOpTy :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => LHsType (GhcPass p) -> LocatedN (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p) #

mkHsAppTys :: forall (p :: Pass). LHsType (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p) #

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

lhsTypeArgSrcSpan :: forall (pass :: Pass). LHsTypeArg (GhcPass pass) -> SrcSpan #

Compute the SrcSpan associated with an LHsTypeArg.

ignoreParens :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) #

hsTypeNeedsParens :: forall (p :: Pass). PprPrec -> HsType (GhcPass p) -> Bool #

hsTypeNeedsParens p t returns True if the type t needs parentheses under precedence p.

hsTyVarName :: forall flag (p :: Pass). HsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p) #

hsTyVarBndrFlag :: forall flag (pass :: Pass). HsTyVarBndr flag (GhcPass pass) -> flag #

Return the attached flag

hsTyKindSig :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (LHsKind (GhcPass p)) #

Get the kind signature of a type, ignoring parentheses:

hsTyKindSig `Maybe ` = Nothing hsTyKindSig `Maybe :: Type -> Type ` = Just `Type -> Type` hsTyKindSig `Maybe :: ((Type -> Type))` = Just `Type -> Type`

This is used to extract the result kind of type synonyms with a CUSK:

type S = (F :: res_kind) ^^^^^^^^

hsTyGetAppHead_maybe :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => LHsType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p))) #

Retrieve the name of the "head" of a nested type application. This is somewhat like GHC.Tc.Gen.HsType.splitHsAppTys, but a little more thorough. The purpose of this function is to examine instance heads, so it doesn't handle *all* cases (like lists, tuples, (~), etc.).

hsTvbAllKinded :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> Bool #

Do all type variables in this LHsQTyVars come with kind annotations?

hsOuterExplicitBndrs :: forall flag (p :: Pass). HsOuterTyVarBndrs flag (GhcPass p) -> [LHsTyVarBndr flag (NoGhcTc (GhcPass p))] #

hsLTyVarNames :: forall flag (p :: Pass). [LHsTyVarBndr flag (GhcPass p)] -> [IdP (GhcPass p)] #

hsLTyVarName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p) #

hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LocatedN (IdP (GhcPass p))] #

hsLTyVarLocName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> LocatedN (IdP (GhcPass p)) #

hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)] #

getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p) #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into the instance_head.

getLHsInstDeclClass_maybe :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => LHsSigType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p))) #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into the instance_head and retrieve the underlying class type constructor (if it exists).

getBangType :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) #

getBangStrictness :: forall (p :: Pass). LHsType (GhcPass p) -> HsSrcBang #

arrowToHsType :: HsArrow GhcRn -> LHsType GhcRn #

Convert an arrow into its corresponding multiplicity. In essence this erases the information of whether the programmer wrote an explicit multiplicity or a shorthand.

data OverLitTc #

Constructors

OverLitTc 

Instances

Instances details
Data OverLitTc 
Instance details

Defined in GHC.Hs.Lit

Methods

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

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

toConstr :: OverLitTc -> Constr #

dataTypeOf :: OverLitTc -> DataType #

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

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

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

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

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

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

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

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

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

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

pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc #

pmPprHsLit pretty prints literals and is used when pretty printing pattern match warnings. All are printed the same (i.e., without hashes if they are primitive and not wrapped in constructors if they are boxed). This happens mainly for too reasons: * We do not want to expose their internal representation * The warnings become too messy

convertLit :: forall (p1 :: Pass) (p2 :: Pass). HsLit (GhcPass p1) -> HsLit (GhcPass p2) #

Convert a literal from one index type to another

pprSplice :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc #

pprPatBind :: forall (bndr :: Pass) (p :: Pass). (OutputableBndrId bndr, OutputableBndrId p) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) (LHsExpr (GhcPass p)) -> SDoc #

pprLExpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc #

pprFunBind :: forall (idR :: Pass). OutputableBndrId idR => MatchGroup (GhcPass idR) (LHsExpr (GhcPass idR)) -> SDoc #

pprExpr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc #

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
ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

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
ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (HsTupArg GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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.

Instances

Instances details
ExactPrint (HsPragE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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
ExactPrint (HsCmdTop GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsCmd GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsCmd GhcPs -> Entry #

setAnnotationAnchor :: HsCmd GhcPs -> Anchor -> EpAnnComments -> HsCmd GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsCmd GhcPs -> EP w m (HsCmd GhcPs) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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) 

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
ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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) 

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) 

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
ExactPrint (WarnDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (WarnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (TyFamInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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
ExactPrint (TyClDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (TyClDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data SpliceDecl p #

Splice Declaration

Instances

Instances details
ExactPrint (SpliceDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (RuleDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (RuleDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (RuleDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RuleBndr pass #

Rule Binder

Instances

Instances details
ExactPrint (RuleBndr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (RuleBndr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data RoleAnnotDecl pass #

Role Annotation Declaration

Instances

Instances details
ExactPrint (RoleAnnotDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (InstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (InjectivityAnn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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) 

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
ExactPrint (HsDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsDecl GhcPs -> Entry #

setAnnotationAnchor :: HsDecl GhcPs -> Anchor -> EpAnnComments -> HsDecl GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsDecl GhcPs -> EP w m (HsDecl GhcPs) #

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) 

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

data FunDep pass #

Constructors

FunDep (XCFunDep pass) [LIdP pass] [LIdP pass] 
XFunDep !(XXFunDep pass) 

Instances

Instances details
ExactPrint (FunDep GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FunDep GhcPs -> Entry #

setAnnotationAnchor :: FunDep GhcPs -> Anchor -> EpAnnComments -> FunDep GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FunDep GhcPs -> EP w m (FunDep GhcPs) #

type Anno (FunDep (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

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 #

ExactPrint ForeignImport 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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 #

ExactPrint ForeignExport 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

data ForeignDecl pass #

Foreign Declaration

Instances

Instances details
ExactPrint (ForeignDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (ForeignDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data FamilyResultSig pass #

type Family Result Signature

Instances

Instances details
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 #

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
ExactPrint body => ExactPrint (FamEqn GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FamEqn GhcPs body -> Entry #

setAnnotationAnchor :: FamEqn GhcPs body -> Anchor -> EpAnnComments -> FamEqn GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FamEqn GhcPs body -> EP w m (FamEqn GhcPs body) #

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 #

ExactPrint DocDecl 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: DocDecl -> Entry #

setAnnotationAnchor :: DocDecl -> Anchor -> EpAnnComments -> DocDecl #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DocDecl -> EP w m DocDecl #

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
ExactPrint (DerivStrategy GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (DerivDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (DerivClauseTys GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (DerivClauseTys (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

data DefaultDecl pass #

Default Declaration

Instances

Instances details
ExactPrint (DefaultDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (DefaultDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

newtype DataFamInstDecl pass #

Data Family Instance Declaration

Instances

Instances details
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
ExactPrint (ConDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (ConDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.Decls

data ClsInstDecl pass #

Class Instance Declaration

Instances

Instances details
ExactPrint (ClsInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

data AnnDecl pass #

Annotation Declaration

Instances

Instances details
ExactPrint (AnnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (Sig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Sig GhcPs -> Entry #

setAnnotationAnchor :: Sig GhcPs -> Anchor -> EpAnnComments -> Sig GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Sig GhcPs -> EP w m (Sig GhcPs) #

type Anno (Sig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data RecordPatSynField pass #

Record Pattern Synonym Field

Constructors

RecordPatSynField 

Fields

data PatSynBind idL idR #

Pattern Synonym binding

Constructors

PSB 

Fields

XPatSynBind !(XXPatSynBind idL idR) 

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
ExactPrint (IPBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IPBind GhcPs -> Entry #

setAnnotationAnchor :: IPBind GhcPs -> Anchor -> EpAnnComments -> IPBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IPBind GhcPs -> EP w m (IPBind GhcPs) #

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.

type HsValBinds id = HsValBindsLR id id #

Haskell Value Bindings

data HsPatSynDir id #

Haskell Pattern Synonym Direction

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) 

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) 

Instances

Instances details
ExactPrint (HsIPBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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
ExactPrint (HsBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsBind GhcPs -> Entry #

setAnnotationAnchor :: HsBind GhcPs -> Anchor -> EpAnnComments -> HsBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsBind GhcPs -> EP w m (HsBind GhcPs) #

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

pprLPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> 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
(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 #

ExactPrint body => ExactPrint (HsRecFields GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsRecFields GhcPs body -> Entry #

setAnnotationAnchor :: HsRecFields GhcPs body -> Anchor -> EpAnnComments -> HsRecFields GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsRecFields GhcPs body -> EP w m (HsRecFields GhcPs body) #

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 #

(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsRecField' p arg) 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsRecField' p arg -> SDoc #

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint body => ExactPrint (HsRecField' (FieldLabelStrings GhcPs) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsRecField' (FieldOcc GhcPs) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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) 

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
ExactPrint body => ExactPrint (HsWildCardBndrs GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

ExactPrint (HsType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsType GhcPs -> Entry #

setAnnotationAnchor :: HsType GhcPs -> Anchor -> EpAnnComments -> HsType GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsType GhcPs -> EP w m (HsType GhcPs) #

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
ExactPrintTVFlag flag => ExactPrint (HsTyVarBndr flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsTyVarBndr flag GhcPs -> Entry #

setAnnotationAnchor :: HsTyVarBndr flag GhcPs -> Anchor -> EpAnnComments -> HsTyVarBndr flag GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsTyVarBndr flag GhcPs -> EP w m (HsTyVarBndr flag GhcPs) #

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
ExactPrint (HsSigType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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 #

ExactPrint a => ExactPrint (HsScaled GhcPs a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsScaled GhcPs a -> Entry #

setAnnotationAnchor :: HsScaled GhcPs a -> Anchor -> EpAnnComments -> HsScaled GhcPs a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsScaled GhcPs a -> EP w m (HsScaled GhcPs a) #

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) 

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
ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

ExactPrint HsIPName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsIPName -> Entry #

setAnnotationAnchor :: HsIPName -> Anchor -> EpAnnComments -> HsIPName #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsIPName -> EP w m HsIPName #

Eq HsIPName 
Instance details

Defined in Language.Haskell.Syntax.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 #

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 #

(ExactPrint tm, ExactPrint ty, Outputable tm, Outputable ty) => ExactPrint (HsArg tm ty) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsArg tm ty -> Entry #

setAnnotationAnchor :: HsArg tm ty -> Anchor -> EpAnnComments -> HsArg tm ty #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsArg tm ty -> EP w m (HsArg tm ty) #

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

ExactPrint (FieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) 
Instance details

Defined in Language.Haskell.Syntax.Type

ExactPrint body => ExactPrint (HsRecField' (FieldOcc GhcPs) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

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

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.

pat_con :: Pat p -> XRec p (ConLikeP p) #

pattern XPat :: !(XXPat p) -> Pat p #

Trees that Grow extension point for new constructors

pattern WildPat :: XWildPat p -> Pat p #

Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type

pattern ViewPat #

Arguments

:: XViewPat p 
-> LHsExpr p 
-> LPat p

View Pattern

-> Pat p 

pattern VarPat :: XVarPat p -> LIdP p -> Pat p #

Variable Pattern

pattern TuplePat :: XTuplePat p -> [LPat p] -> Boxity -> Pat p #

Tuple sub-patterns

pattern SumPat :: XSumPat p -> LPat p -> ConTag -> Arity -> Pat p #

Anonymous sum pattern

pattern SplicePat #

Arguments

:: XSplicePat p 
-> HsSplice p

Splice Pattern (Includes quasi-quotes)

-> Pat p 

pattern SigPat #

Arguments

:: XSigPat p 
-> LPat p 
-> HsPatSigType (NoGhcTc p)

Pattern with a type signature

-> Pat p 

pattern ParPat :: XParPat p -> LPat p -> Pat p #

Parenthesised pattern See Note [Parens in HsSyn] in GHC.Hs.Expr ^ - AnnKeywordId : AnnOpen '(', AnnClose ')'

pattern NPlusKPat :: XNPlusKPat p -> LIdP p -> XRec p (HsOverLit p) -> HsOverLit p -> SyntaxExpr p -> SyntaxExpr p -> Pat p #

n+k pattern

pattern NPat :: XNPat p -> XRec p (HsOverLit p) -> Maybe (SyntaxExpr p) -> SyntaxExpr p -> Pat p #

Natural Pattern

pattern LitPat :: XLitPat p -> HsLit p -> Pat p #

Literal Pattern Used for *non-overloaded* literal patterns: Int#, Char#, Int, Char, String, etc.

pattern ListPat :: XListPat p -> [LPat p] -> Pat p #

Syntactic List

pattern LazyPat :: XLazyPat p -> LPat p -> Pat p #

Lazy Pattern ^ - AnnKeywordId : AnnTilde

pattern ConPat :: XConPat p -> XRec p (ConLikeP p) -> HsConPatDetails p -> Pat p #

Constructor Pattern

pattern AsPat :: XAsPat p -> LIdP p -> LPat p -> Pat p #

As pattern ^ - AnnKeywordId : AnnAt

pattern BangPat :: XBangPat p -> LPat p -> Pat p #

Bang pattern ^ - AnnKeywordId : AnnBang

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
ExactPrint (HsOverLit GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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 LImportDecl pass #

Arguments

 = XRec pass (ImportDecl pass)

When in a list this may have

Located Import Declaration

type LIEWrappedName name = LocatedA (IEWrappedName name) #

Located name with possible adornment - AnnKeywordIds : AnnType, AnnPattern

type LIE pass #

Arguments

 = XRec pass (IE pass)

When in a list this may have

Located Import or Export

data ImportDeclQualifiedStyle #

If/how an import is qualified.

Constructors

QualifiedPre

qualified appears in prepositive position.

QualifiedPost

qualified appears in postpositive position.

NotQualified

Not qualified.

Instances

Instances details
Data ImportDeclQualifiedStyle 
Instance details

Defined in GHC.Hs.ImpExp

Methods

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

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

toConstr :: ImportDeclQualifiedStyle -> Constr #

dataTypeOf :: ImportDeclQualifiedStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ImportDeclQualifiedStyle 
Instance details

Defined in GHC.Hs.ImpExp

data ImportDecl pass #

Import Declaration

A single Haskell import declaration.

Constructors

ImportDecl 

Fields

XImportDecl !(XXImportDecl pass)

AnnKeywordIds

Instances

Instances details
(OutputableBndrId p, Outputable (Anno (IE (GhcPass p)))) => Outputable (ImportDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: ImportDecl (GhcPass p) -> SDoc #

ExactPrint (ImportDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (ImportDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

data IEWrappedName name #

A name in an import or export specification which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement. The Annotation is the location of the adornment in the original source.

Constructors

IEName (LocatedN name)

no extra

IEPattern EpaLocation (LocatedN name)

pattern X

IEType EpaLocation (LocatedN name)

type (:+:)

Instances

Instances details
Data name => Data (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

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

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

toConstr :: IEWrappedName name -> Constr #

dataTypeOf :: IEWrappedName name -> DataType #

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

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

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

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

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

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

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

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

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

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

HasOccName name => HasOccName (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

occName :: IEWrappedName name -> OccName #

OutputableBndr name => Outputable (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IEWrappedName name -> SDoc #

OutputableBndr name => OutputableBndr (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

ExactPrint (IEWrappedName RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Eq name => Eq (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

(==) :: IEWrappedName name -> IEWrappedName name -> Bool #

(/=) :: IEWrappedName name -> IEWrappedName name -> Bool #

data IEWildcard #

Imported or Exported Wildcard

Constructors

NoIEWildcard 
IEWildcard Int 

Instances

Instances details
Data IEWildcard 
Instance details

Defined in GHC.Hs.ImpExp

Methods

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

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

toConstr :: IEWildcard -> Constr #

dataTypeOf :: IEWildcard -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq IEWildcard 
Instance details

Defined in GHC.Hs.ImpExp

data IE pass #

Imported or exported entity.

Constructors

IEVar (XIEVar pass) (LIEWrappedName (IdP pass))

Imported or Exported Variable

IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass))

Imported or exported Thing with Absent list

The thing is a Class/Type (can't tell) - AnnKeywordIds : AnnPattern, AnnType,AnnVal

IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))

Imported or exported Thing with All imported or exported

The thing is a ClassType and the All refers to methodsconstructors

IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)]

Imported or exported Thing With given imported or exported

The thing is a Class/Type and the imported or exported things are methods/constructors and record fields; see Note [IEThingWith] - AnnKeywordIds : AnnOpen, AnnClose, AnnComma, AnnType

IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)

Imported or exported module contents

(Export Only)

IEGroup (XIEGroup pass) Int HsDocString

Doc section heading

IEDoc (XIEDoc pass) HsDocString

Some documentation

IEDocNamed (XIEDocNamed pass) String

Reference to named doc

XIE !(XXIE pass) 

Instances

Instances details
OutputableBndrId p => Outputable (IE (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IE (GhcPass p) -> SDoc #

ExactPrint (IE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IE GhcPs -> Entry #

setAnnotationAnchor :: IE GhcPs -> Anchor -> EpAnnComments -> IE GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IE GhcPs -> EP w m (IE GhcPs) #

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno (IE (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IE (GhcPass p)) = SrcSpanAnnA
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

data EpAnnImportDecl #

Instances

Instances details
Data EpAnnImportDecl 
Instance details

Defined in GHC.Hs.ImpExp

Methods

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

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

toConstr :: EpAnnImportDecl -> Constr #

dataTypeOf :: EpAnnImportDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2 #

pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc #

isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool #

Convenience function to answer the question if an import decl. is qualified.

importDeclQualifiedStyle :: Maybe EpaLocation -> Maybe EpaLocation -> (Maybe EpaLocation, ImportDeclQualifiedStyle) #

Given two possible located qualified tokens, compute a style (in a conforming Haskell program only one of the two can be not Nothing). This is called from GHC.Parser.

ieWrappedName :: IEWrappedName name -> name #

ieNames :: forall (p :: Pass). IE (GhcPass p) -> [IdP (GhcPass p)] #

ieName :: forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p) #

data Pass #

Constructors

Parsed 
Renamed 
Typechecked 

Instances

Instances details
Data Pass 
Instance details

Defined in GHC.Hs.Extension

Methods

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

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

toConstr :: Pass -> Constr #

dataTypeOf :: Pass -> DataType #

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

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

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

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

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

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

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

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

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

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

type OutputableBndrId (pass :: Pass) = (OutputableBndr (IdGhcP pass), OutputableBndr (IdGhcP (NoGhcTcPass pass)), Outputable (GenLocated (Anno (IdGhcP pass)) (IdGhcP pass)), Outputable (GenLocated (Anno (IdGhcP (NoGhcTcPass pass))) (IdGhcP (NoGhcTcPass pass))), IsPass pass) #

Constraint type to bundle up the requirement for OutputableBndr on both the id and the NoGhcTc of it. See Note [NoGhcTc].

type family NoGhcTcPass (p :: Pass) :: Pass where ... #

Equations

NoGhcTcPass 'Typechecked = 'Renamed 
NoGhcTcPass other = other 

type IsSrcSpanAnn (p :: Pass) a = (Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a), IsPass p) #

class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass (p :: Pass) where #

Allows us to check what phase we're in at GHC's runtime. For example, this class allows us to write > f :: forall p. IsPass p => HsExpr (GhcPass p) -> blah > f e = case ghcPass @p of > GhcPs -> ... in this RHS we have HsExpr GhcPs... > GhcRn -> ... in this RHS we have HsExpr GhcRn... > GhcTc -> ... in this RHS we have HsExpr GhcTc... which is very useful, for example, when pretty-printing. See Note [IsPass].

Methods

ghcPass :: GhcPass p #

Instances

Instances details
IsPass 'Parsed 
Instance details

Defined in GHC.Hs.Extension

Methods

ghcPass :: GhcPass 'Parsed #

IsPass 'Renamed 
Instance details

Defined in GHC.Hs.Extension

IsPass 'Typechecked 
Instance details

Defined in GHC.Hs.Extension

type family IdGhcP (pass :: Pass) where ... #

Maps the "normal" id type for a given GHC pass

data GhcPass (c :: Pass) where #

Used as a data type index for the hsSyn AST; also serves as a singleton type for Pass

Instances

Instances details
Typeable p => Data (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

Methods

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

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

toConstr :: GhcPass p -> Constr #

dataTypeOf :: GhcPass p -> DataType #

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

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

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

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

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

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

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

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

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

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

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

DisambECP (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (PatBuilder GhcPs) :: Type -> Type #

type InfixOp (PatBuilder GhcPs) #

type FunArg (PatBuilder GhcPs) #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (PatBuilder GhcPs)) #

ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (PatBuilder GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (PatBuilder GhcPs))) #

mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (PatBuilder GhcPs) -> AnnsLet -> PV (LocatedA (PatBuilder GhcPs)) #

superInfixOp :: (DisambInfixOp (InfixOp (PatBuilder GhcPs)) => PV (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsOpAppPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> LocatedN (InfixOp (PatBuilder GhcPs)) -> LocatedA (PatBuilder GhcPs) -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (PatBuilder GhcPs))] -> EpAnnHsCase -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (PatBuilder GhcPs))] -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

superFunArg :: (DisambECP (FunArg (PatBuilder GhcPs)) => PV (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsAppPV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> LocatedA (FunArg (PatBuilder GhcPs)) -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (PatBuilder GhcPs) -> Bool -> LocatedA (PatBuilder GhcPs) -> AnnsIf -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (PatBuilder GhcPs))] -> AnnList -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsParPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> AnnParen -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (PatBuilder GhcPs)) #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (PatBuilder GhcPs)) #

mkHsWildCardPV :: SrcSpan -> PV (Located (PatBuilder GhcPs)) #

mkHsTySigPV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsExplicitListPV :: SrcSpan -> [LocatedA (PatBuilder GhcPs)] -> AnnList -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (PatBuilder GhcPs)) #

mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (PatBuilder GhcPs) -> ([Fbind (PatBuilder GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsNegAppPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (PatBuilder GhcPs)) -> LocatedA (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsLazyPatPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkHsBangPatPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) #

rejectPragmaPV :: LocatedA (PatBuilder GhcPs) -> PV () #

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

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

DisambTD (HsType GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

OutputableBndrId p => Outputable (IE (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IE (GhcPass p) -> SDoc #

(OutputableBndrId p, Outputable (Anno (IE (GhcPass p)))) => Outputable (ImportDecl (GhcPass p)) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: ImportDecl (GhcPass p) -> SDoc #

Outputable (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.Types

Methods

ppr :: PatBuilder GhcPs -> SDoc #

OutputableBndrId a => Outputable (InstInfo (GhcPass a)) 
Instance details

Defined in GHC.Tc.Utils.Env

Methods

ppr :: InstInfo (GhcPass a) -> SDoc #

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 #

UnXRec (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

Methods

unXRec :: XRec (GhcPass p) a -> a #

ExactPrint (IE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IE GhcPs -> Entry #

setAnnotationAnchor :: IE GhcPs -> Anchor -> EpAnnComments -> IE GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IE GhcPs -> EP w m (IE GhcPs) #

ExactPrint (ImportDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsBind GhcPs -> Entry #

setAnnotationAnchor :: HsBind GhcPs -> Anchor -> EpAnnComments -> HsBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsBind GhcPs -> EP w m (HsBind GhcPs) #

ExactPrint (HsIPBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsLocalBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (IPBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IPBind GhcPs -> Entry #

setAnnotationAnchor :: IPBind GhcPs -> Anchor -> EpAnnComments -> IPBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IPBind GhcPs -> EP w m (IPBind GhcPs) #

ExactPrint (RecordPatSynField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Sig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Sig GhcPs -> Entry #

setAnnotationAnchor :: Sig GhcPs -> Anchor -> EpAnnComments -> Sig GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Sig GhcPs -> EP w m (Sig GhcPs) #

ExactPrint (AnnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ClsInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ConDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DefaultDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivClauseTys GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivStrategy GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FamilyDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ForeignDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FunDep GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FunDep GhcPs -> Entry #

setAnnotationAnchor :: FunDep GhcPs -> Anchor -> EpAnnComments -> FunDep GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FunDep GhcPs -> EP w m (FunDep GhcPs) #

ExactPrint (HsDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsDecl GhcPs -> Entry #

setAnnotationAnchor :: HsDecl GhcPs -> Anchor -> EpAnnComments -> HsDecl GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsDecl GhcPs -> EP w m (HsDecl GhcPs) #

ExactPrint (HsDerivingClause GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (InjectivityAnn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (InstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RoleAnnotDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleBndr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (SpliceDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (StandaloneKindSig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (TyClDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (TyFamInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (WarnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (WarnDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FieldLabelStrings GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsCmd GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsCmd GhcPs -> Entry #

setAnnotationAnchor :: HsCmd GhcPs -> Anchor -> EpAnnComments -> HsCmd GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsCmd GhcPs -> EP w m (HsCmd GhcPs) #

ExactPrint (HsCmdTop GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsExpr GhcPs -> Entry #

setAnnotationAnchor :: HsExpr GhcPs -> Anchor -> EpAnnComments -> HsExpr GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsExpr GhcPs -> EP w m (HsExpr GhcPs) #

ExactPrint (HsFieldLabel GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsPragE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsSplice GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsTupArg GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsOverLit GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Pat GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Pat GhcPs -> Entry #

setAnnotationAnchor :: Pat GhcPs -> Anchor -> EpAnnComments -> Pat GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Pat GhcPs -> EP w m (Pat GhcPs) #

ExactPrint (AmbiguousFieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ConDeclField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsForAllTelescope GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsPatSigType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsSigType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsType GhcPs -> Entry #

setAnnotationAnchor :: HsType GhcPs -> Anchor -> EpAnnComments -> HsType GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsType GhcPs -> EP w m (HsType GhcPs) #

ExactPrint (NonEmpty (Located (HsFieldLabel GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint (HsValBindsLR GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (PatSynBind GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (FamEqn GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FamEqn GhcPs body -> Entry #

setAnnotationAnchor :: FamEqn GhcPs body -> Anchor -> EpAnnComments -> FamEqn GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FamEqn GhcPs body -> EP w m (FamEqn GhcPs body) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ParStmtBlock GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsRecField' (FieldLabelStrings GhcPs) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsRecField' (FieldOcc GhcPs) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsRecFields GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsRecFields GhcPs body -> Entry #

setAnnotationAnchor :: HsRecFields GhcPs body -> Anchor -> EpAnnComments -> HsRecFields GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsRecFields GhcPs body -> EP w m (HsRecFields GhcPs body) #

ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (HsScaled GhcPs a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsScaled GhcPs a -> Entry #

setAnnotationAnchor :: HsScaled GhcPs a -> Anchor -> EpAnnComments -> HsScaled GhcPs a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsScaled GhcPs a -> EP w m (HsScaled GhcPs a) #

ExactPrintTVFlag flag => ExactPrint (HsTyVarBndr flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsTyVarBndr flag GhcPs -> Entry #

setAnnotationAnchor :: HsTyVarBndr flag GhcPs -> Anchor -> EpAnnComments -> HsTyVarBndr flag GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsTyVarBndr flag GhcPs -> EP w m (HsTyVarBndr flag GhcPs) #

ExactPrint body => ExactPrint (HsWildCardBndrs GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

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 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 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 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 Body (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Body (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Body (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsCmd GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type HsBracketRn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type HsDoRn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type HsDoRn (GhcPass _1) = GhcRn
type PendingRnSplice' (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type PendingTcSplice' (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type SyntaxExpr (GhcPass p) 
Instance details

Defined in GHC.Hs.Expr

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 (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 [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 IdP (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p
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)
type XABE (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XAnnD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XApp (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _1) = EpAnnCO
type XAppKindTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XAppTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XApplicativeArgMany (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XBangTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XBinTick (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XBracket (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCDerivDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCFamilyDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCFunDep (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCHsDataDefn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCHsDerivingClause (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCHsFieldLabel (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCHsGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCIPBind (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XCInjectivityAnn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCKindSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCRuleBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCTyClGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCTyFamInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XClassOpSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XClsInstD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCmdApp (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCmdApp (GhcPass _1) = EpAnnCO
type XCmdLam (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCmdLamCase (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCmdPar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCmdWrap (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XCompleteMatchSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XConDeclField (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XConDeclGADT (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XConDeclH98 (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XConLikeOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XConLikeOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XDctMulti (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XDctSingle (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XDecBrG (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XDecBrL (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XDefD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XDerivD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XDocD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XDocTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XExpBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XFamDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XFixSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XFixitySig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XForAllTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XForD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XFunTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XHsAnnotation (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XHsChar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsCharPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsDoublePrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsFloatPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsForAllInvis (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XHsForAllVis (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XHsInt (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsInt64Prim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsIntPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsInteger (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsRat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XHsString (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsStringPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsWord64Prim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XHsWordPrim (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XIEDoc (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEDocNamed (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAbs (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAll (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

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 XIPVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XIPVar (GhcPass _1) = EpAnnCO
type XIParamTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XIdSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XInlineSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XInstD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XKindSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XKindSigD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XKindedTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

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 XLamCase (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XListTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XLitE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XLitE (GhcPass _1) = EpAnnCO
type XLitPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type XMinimalSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XNoSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XOpTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XOverLitE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XParPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type XParTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XPatBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XPatSynSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XPragE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XPresent (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _1) = EpAnn [AddEpAnn]
type XQualTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XQuasiQuote (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XRecFld (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XRecFld (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XRnBracketOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XRoleAnnotD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XRuleBndrSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XRuleD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XSCC (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XSCCFunSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XSigD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XSpecInstSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XSpecSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XSpliceD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XSpliceDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XSpliceE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XSplicePat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type XSpliced (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XStarTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XSumTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XTExpBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XTcBracketOut (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XTick (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XTupleTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XTyClD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XTyLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XTyVarSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XTypBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XTypeSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XTypedSplice (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XUntypedSplice (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XUserTyVar (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XValD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

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 XVarBr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XVarPat (GhcPass _1) 
Instance details

Defined in GHC.Hs.Pat

type XWarning (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XWarningD (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XWildCardTy (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXABExport (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XXAmbiguousFieldOcc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXAnnDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXApplicativeArg (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXBracket (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXClsInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXCmdTop (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXConDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXConDeclField (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXDefaultDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXDerivClauseTys (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXDerivDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyResultSig (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXFieldOcc (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXFixitySig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XXForeignDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXFunDep (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXHsDataDefn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXHsDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXHsDerivingClause (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXHsFieldLabel (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXHsForAllTelescope (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXHsGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXHsIPBinds (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XXHsOuterTyVarBndrs (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXHsPatSigType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXHsSigType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXIE (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _1) = NoExtCon
type XXIPBind (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XXImportDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.ImpExp

type XXInjectivityAnn (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXLHsQTyVars (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XXLit (GhcPass _1) = NoExtCon
type XXOverLit (GhcPass _1) 
Instance details

Defined in GHC.Hs.Lit

type XXPragE (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXRoleAnnotDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXRuleBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecls (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Binds

type XXSpliceDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXStandaloneKindSig (GhcPass p) 
Instance details

Defined in GHC.Hs.Decls

type XXTupArg (GhcPass _1) 
Instance details

Defined in GHC.Hs.Expr

type XXTyClDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXTyClGroup (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXTyFamInstDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXTyVarBndr (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXType (GhcPass _1) 
Instance details

Defined in GHC.Hs.Type

type XXType (GhcPass _1) = HsCoreTy
type XXWarnDecl (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XXWarnDecls (GhcPass _1) 
Instance details

Defined in GHC.Hs.Decls

type XCFamEqn (GhcPass _1) r 
Instance details

Defined in GHC.Hs.Decls

type XCFamEqn (GhcPass _1) r = EpAnn [AddEpAnn]
type XCGRHS (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type XCGRHS (GhcPass _1) _2 = EpAnn GrhsAnn
type XCGRHSs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b = EpAnn [AddEpAnn]
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 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 XRec (GhcPass p) a 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) a = GenLocated (Anno a) a
type XXFamEqn (GhcPass _1) r 
Instance details

Defined in GHC.Hs.Decls

type XXFamEqn (GhcPass _1) r = NoExtCon
type XXGRHS (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _1) b = NoExtCon
type XXGRHSs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _1) _2 = NoExtCon
type XXHsWildCardBndrs (GhcPass _1) _2 
Instance details

Defined in GHC.Hs.Type

type XXMatch (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _1) b = NoExtCon
type XXMatchGroup (GhcPass _1) b 
Instance details

Defined in GHC.Hs.Expr

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 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 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 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 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 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 XAbsBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XHsIPBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XHsValBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XParStmtBlock (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Expr

type XPatSynBind (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XValBinds (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XVarBind (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XXHsBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XXParStmtBlock (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Expr

type XXPatSynBind (GhcPass idL) (GhcPass idR) 
Instance details

Defined in GHC.Hs.Binds

type XXValBindsLR (GhcPass pL) (GhcPass pR) 
Instance details

Defined in GHC.Hs.Binds

type XLastStmt (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField
type XLetStmt (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = EpAnn [AddEpAnn]
type XXStmtLR (GhcPass _1) (GhcPass _2) b 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon
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 (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 (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 (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

pprIfTc :: forall (p :: Pass). IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc #

pprIfRn :: forall (p :: Pass). IsPass p => (p ~ 'Renamed => SDoc) -> SDoc #

pprIfPs :: forall (p :: Pass). IsPass p => (p ~ 'Parsed => SDoc) -> SDoc #

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

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
ExactPrint (HsSplice GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsExpr GhcPs -> Entry #

setAnnotationAnchor :: HsExpr GhcPs -> Anchor -> EpAnnComments -> HsExpr GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsExpr GhcPs -> EP w m (HsExpr GhcPs) #

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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) 

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

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 LHsDocString = Located HsDocString #

Located Haskell Documentation String

data HsDocString #

Haskell Documentation String

Internally this is a UTF8-Encoded ByteString.

Instances

Instances details
Data HsDocString 
Instance details

Defined in GHC.Hs.Doc

Methods

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

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

toConstr :: HsDocString -> Constr #

dataTypeOf :: HsDocString -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HsDocString 
Instance details

Defined in GHC.Hs.Doc

Binary HsDocString 
Instance details

Defined in GHC.Hs.Doc

Outputable HsDocString 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: HsDocString -> SDoc #

ExactPrint HsDocString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Eq HsDocString 
Instance details

Defined in GHC.Hs.Doc

data ExtractedTHDocs #

Maps of docs that were added via Template Haskell's putDoc.

Constructors

ExtractedTHDocs 

Fields

newtype DeclDocMap #

Docs for declarations: functions, data types, instances, methods etc.

Constructors

DeclDocMap (Map Name HsDocString) 

Instances

Instances details
Binary DeclDocMap 
Instance details

Defined in GHC.Hs.Doc

Outputable DeclDocMap 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: DeclDocMap -> SDoc #

newtype ArgDocMap #

Docs for arguments. E.g. function arguments, method arguments.

Constructors

ArgDocMap (Map Name (IntMap HsDocString)) 

Instances

Instances details
Binary ArgDocMap 
Instance details

Defined in GHC.Hs.Doc

Outputable ArgDocMap 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: ArgDocMap -> SDoc #

hsDocStringToByteString :: HsDocString -> ByteString #

Return the contents of a HsDocString as a UTF8-encoded ByteString.

concatDocs :: [HsDocString] -> Maybe HsDocString #

Concat docstrings with two newlines in between.

Empty docstrings are skipped.

If all inputs are empty, Nothing is returned.

appendDocs :: HsDocString -> HsDocString -> HsDocString #

Join two docstrings.

Non-empty docstrings are joined with two newlines in between, resulting in separate paragraphs.

data TrailingAnn #

Captures the location of punctuation occuring between items, normally in a list. It is captured as a trailing annotation.

Constructors

AddSemiAnn EpaLocation

Trailing ';'

AddCommaAnn EpaLocation

Trailing ','

AddVbarAnn EpaLocation

Trailing '|'

AddRarrowAnn EpaLocation

Trailing ->

AddRarrowAnnU EpaLocation

Trailing ->, unicode variant

AddLollyAnnU EpaLocation

Trailing

Instances

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

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

toConstr :: TrailingAnn -> Constr #

dataTypeOf :: TrailingAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TrailingAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: TrailingAnn -> SDoc #

Eq TrailingAnn 
Instance details

Defined in GHC.Parser.Annotation

Ord TrailingAnn 
Instance details

Defined in GHC.Parser.Annotation

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.

Constructors

SrcSpanAnn 

Fields

Instances

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

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 #

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (LocatedA a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedA a -> Entry #

setAnnotationAnchor :: LocatedA a -> Anchor -> EpAnnComments -> LocatedA a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedA a -> EP w m (LocatedA a) #

ExactPrint a => ExactPrint (LocatedC a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedC a -> Entry #

setAnnotationAnchor :: LocatedC a -> Anchor -> EpAnnComments -> LocatedC a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedC a -> EP w m (LocatedC a) #

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP CType) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP WarningTxt) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasEntry (SrcSpanAnn' (EpAnn an)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

fromAnn :: SrcSpanAnn' (EpAnn an) -> Entry

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

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

Defined in GHC.Parser.Annotation

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 #

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

data ParenType #

Detail of the "brackets" used in an AnnParen exact print annotation.

Constructors

AnnParens

'(', ')'

AnnParensHash

'(#', '#)'

AnnParensSquare

'[', ']'

Instances

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

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

toConstr :: ParenType -> Constr #

dataTypeOf :: ParenType -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ParenType 
Instance details

Defined in GHC.Parser.Annotation

Ord ParenType 
Instance details

Defined in GHC.Parser.Annotation

data NoEpAnns #

Constructors

NoEpAnns 

Instances

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

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

toConstr :: NoEpAnns -> Constr #

dataTypeOf :: NoEpAnns -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq NoEpAnns 
Instance details

Defined in GHC.Parser.Annotation

Ord NoEpAnns 
Instance details

Defined in GHC.Parser.Annotation

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 #

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

A NameAnn can capture the locations of surrounding adornments, such as parens or backquotes. This data type identifies what particular pair are being used.

Constructors

NameParens

'(' ')'

NameParensHash

'(#' '#)'

NameBackquotes

'`'

NameSquare

'[' ']'

Instances

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

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

toConstr :: NameAdornment -> Constr #

dataTypeOf :: NameAdornment -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable NameAdornment 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAdornment -> SDoc #

Eq NameAdornment 
Instance details

Defined in GHC.Parser.Annotation

Ord NameAdornment 
Instance details

Defined in GHC.Parser.Annotation

type LocatedAn an = GenLocated (SrcAnn an) #

General representation of a GenLocated type carrying a parameterised annotation type.

data IsUnicodeSyntax #

Certain tokens can have alternate representations when unicode syntax is enabled. This flag is attached to those tokens in the lexer so that the original source representation can be reproduced in the corresponding EpAnnotation

Instances

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

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

toConstr :: IsUnicodeSyntax -> Constr #

dataTypeOf :: IsUnicodeSyntax -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IsUnicodeSyntax 
Instance details

Defined in GHC.Parser.Annotation

Outputable IsUnicodeSyntax 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: IsUnicodeSyntax -> SDoc #

Eq IsUnicodeSyntax 
Instance details

Defined in GHC.Parser.Annotation

Ord IsUnicodeSyntax 
Instance details

Defined in GHC.Parser.Annotation

data HasE #

Some template haskell tokens have two variants, one with an e the other not:

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

This type indicates whether the e is present or not.

Constructors

HasE 
NoE 

Instances

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

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

toConstr :: HasE -> Constr #

dataTypeOf :: HasE -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HasE 
Instance details

Defined in GHC.Parser.Annotation

Methods

showsPrec :: Int -> HasE -> ShowS #

show :: HasE -> String #

showList :: [HasE] -> ShowS #

Eq HasE 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Ord HasE 
Instance details

Defined in GHC.Parser.Annotation

Methods

compare :: HasE -> HasE -> Ordering #

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

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

(>) :: HasE -> HasE -> Bool #

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

max :: HasE -> HasE -> HasE #

min :: HasE -> HasE -> HasE #

data EpaLocation #

The anchor for an AnnKeywordId. The Parser inserts the EpaSpan variant, giving the exact location of the original item in the parsed source. This can be replaced by the EpaDelta version, to provide a position for the item relative to the end of the previous item in the source. This is useful when editing an AST prior to exact printing the changed one. The list of comments in the EpaDelta variant captures any comments between the prior output and the thing being marked here, since we cannot otherwise sort the relative order.

Instances

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

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

toConstr :: EpaLocation -> Constr #

dataTypeOf :: EpaLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable EpaLocation 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaLocation -> SDoc #

Eq EpaLocation 
Instance details

Defined in GHC.Parser.Annotation

Ord EpaLocation 
Instance details

Defined in GHC.Parser.Annotation

data EpaCommentTok #

Constructors

EpaDocCommentNext String

something beginning '-- |'

EpaDocCommentPrev String

something beginning '-- ^'

EpaDocCommentNamed String

something beginning '-- $'

EpaDocSection Int String

a section heading

EpaDocOptions String

doc options (prune, ignore-exports, etc)

EpaLineComment String

comment starting by "--"

EpaBlockComment String

comment in {- -}

EpaEofComment

empty comment, capturing location of EOF

Instances

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

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

toConstr :: EpaCommentTok -> Constr #

dataTypeOf :: EpaCommentTok -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EpaCommentTok 
Instance details

Defined in GHC.Parser.Annotation

Eq EpaCommentTok 
Instance details

Defined in GHC.Parser.Annotation

Ord EpaCommentTok 
Instance details

Defined in GHC.Parser.Annotation

data EpaComment #

Constructors

EpaComment 

Fields

Instances

Instances details
Data EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: EpaComment -> Constr #

dataTypeOf :: EpaComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc #

Eq EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Ord EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Outputable (GenLocated Anchor EpaComment) 
Instance details

Defined in GHC.Parser.Annotation

data EpAnnComments #

When we are parsing we add comments that belong a particular AST element, and print them together with the element, interleaving them into the output stream. But when editing the AST to move fragments around it is useful to be able to first separate the comments into those occuring before the AST element and those following it. The EpaCommentsBalanced constructor is used to do this. The GHC parser will only insert the EpaComments form.

Instances

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

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

toConstr :: EpAnnComments -> Constr #

dataTypeOf :: EpAnnComments -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup EpAnnComments 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpAnnComments 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnnComments -> SDoc #

Eq EpAnnComments 
Instance details

Defined in GHC.Parser.Annotation

type EpAnnCO #

Arguments

 = EpAnn NoEpAnns

Api Annotations for comments only

data EpAnn ann #

The exact print annotations (EPAs) are kept in the HsSyn AST for the GhcPs phase. We do not always have EPAs though, only for code that has been parsed as they do not exist for generated code. This type captures that they may be missing.

A goal of the annotations is that an AST can be edited, including moving subtrees from one place to another, duplicating them, and so on. This means that each fragment must be self-contained. To this end, each annotated fragment keeps track of the anchor position it was originally captured at, being simply the start span of the topmost element of the ast fragment. This gives us a way to later re-calculate all Located items in this layer of the AST, as well as any annotations captured. The comments associated with the AST fragment are also captured here.

The ann type parameter allows this general structure to be specialised to the specific set of locations of original exact print annotation elements. So for HsLet we have

type instance XLet GhcPs = EpAnn AnnsLet data AnnsLet = AnnsLet { alLet :: EpaLocation, alIn :: EpaLocation } deriving Data

The spacing between the items under the scope of a given EpAnn is normally derived from the original Anchor. But if a sub-element is not in its original position, the required spacing can be directly captured in the anchor_op field of the entry Anchor. This allows us to freely move elements around, and stitch together new AST fragments out of old ones, and have them still printed out in a precise way.

Constructors

EpAnn 

Fields

  • entry :: !Anchor

    Base location for the start of the syntactic element holding the annotations.

  • anns :: !ann

    Annotations added by the Parser

  • comments :: !EpAnnComments

    Comments enclosed in the SrcSpan of the element this EpAnn is attached to

EpAnnNotUsed

No Annotation for generated code, e.g. from TH, deriving, etc.

Instances

Instances details
Functor EpAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Data ann => Data (EpAnn ann) 
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) -> EpAnn ann -> c (EpAnn ann) #

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

toConstr :: EpAnn ann -> Constr #

dataTypeOf :: EpAnn ann -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid a => Monoid (EpAnn a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

mempty :: EpAnn a #

mappend :: EpAnn a -> EpAnn a -> EpAnn a #

mconcat :: [EpAnn a] -> EpAnn a #

Semigroup a => Semigroup (EpAnn a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

(<>) :: EpAnn a -> EpAnn a -> EpAnn a #

sconcat :: NonEmpty (EpAnn a) -> EpAnn a #

stimes :: Integral b => b -> EpAnn a -> EpAnn 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 (EpAnn a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnn a -> SDoc #

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (LocatedA a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedA a -> Entry #

setAnnotationAnchor :: LocatedA a -> Anchor -> EpAnnComments -> LocatedA a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedA a -> EP w m (LocatedA a) #

ExactPrint a => ExactPrint (LocatedC a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedC a -> Entry #

setAnnotationAnchor :: LocatedC a -> Anchor -> EpAnnComments -> LocatedC a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedC a -> EP w m (LocatedC a) #

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP CType) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP WarningTxt) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasEntry (EpAnn a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

fromAnn :: EpAnn a -> Entry

HasEntry (SrcSpanAnn' (EpAnn an)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

fromAnn :: SrcSpanAnn' (EpAnn an) -> Entry

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Eq ann => Eq (EpAnn ann) 
Instance details

Defined in GHC.Parser.Annotation

Methods

(==) :: EpAnn ann -> EpAnn ann -> Bool #

(/=) :: EpAnn ann -> EpAnn ann -> Bool #

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 #

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

Spacing between output items when exact printing. It captures the spacing from the current print position on the page to the position required for the thing about to be printed. This is either on the same line in which case is is simply the number of spaces to emit, or it is some number of lines down, with a given column offset. The exact printing algorithm keeps track of the column offset pertaining to the current anchor position, so the deltaColumn is the additional spaces to add in this case. See https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations for details.

Constructors

SameLine 

Fields

DifferentLine 

Fields

Instances

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

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

toConstr :: DeltaPos -> Constr #

dataTypeOf :: DeltaPos -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Outputable DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc #

Eq DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Ord DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

data AnnSortKey #

Captures the sort order of sub elements. This is needed when the sub-elements have been split (as in a HsLocalBind which holds separate binds and sigs) or for infix patterns where the order has been re-arranged. It is captured explicitly so that after the Delta phase a SrcSpan is used purely as an index into the annotations, allowing transformations of the AST including the introduction of new Located items or re-arranging existing ones.

Instances

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

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

toConstr :: AnnSortKey -> Constr #

dataTypeOf :: AnnSortKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid AnnSortKey 
Instance details

Defined in GHC.Parser.Annotation

Semigroup AnnSortKey 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnSortKey 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnSortKey -> SDoc #

Eq AnnSortKey 
Instance details

Defined in GHC.Parser.Annotation

data AnnPragma #

exact print annotation used for capturing the locations of annotations in pragmas.

Constructors

AnnPragma 

Instances

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

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

toConstr :: AnnPragma -> Constr #

dataTypeOf :: AnnPragma -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AnnPragma 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnPragma -> SDoc #

Eq AnnPragma 
Instance details

Defined in GHC.Parser.Annotation

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP CType) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP WarningTxt) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

data AnnParen #

exact print annotation for an item having surrounding "brackets", such as tuples or lists

Instances

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

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

toConstr :: AnnParen -> Constr #

dataTypeOf :: AnnParen -> DataType #

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

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

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

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

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

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

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

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

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

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

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

ExactPrint a => ExactPrint (LocatedA a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedA a -> Entry #

setAnnotationAnchor :: LocatedA a -> Anchor -> EpAnnComments -> LocatedA a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedA a -> EP w m (LocatedA a) #

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.

Constructors

AnnList 

Fields

Instances

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

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

toConstr :: AnnList -> Constr #

dataTypeOf :: AnnList -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid AnnList 
Instance details

Defined in GHC.Parser.Annotation

Semigroup AnnList 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnList 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnList -> SDoc #

Eq AnnList 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

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

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

data AnnKeywordId #

Exact print annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not otherwise captured in the AST.

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

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

Constructors

AnnAnyclass 
AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseB

'|)'

AnnCloseBU

'|)', unicode variant

AnnCloseC

'}'

AnnCloseQ

'|]'

AnnCloseQU

'|]', unicode variant

AnnCloseP

')'

AnnClosePH

'#)'

AnnCloseS

']'

AnnColon 
AnnComma

as a list separator

AnnCommaTuple

in a RdrName for a tuple

AnnDarrow

'=>'

AnnDarrowU

'=>', unicode variant

AnnData 
AnnDcolon

'::'

AnnDcolonU

'::', unicode variant

AnnDefault 
AnnDeriving 
AnnDo 
AnnDot

.

AnnDotdot

'..'

AnnElse 
AnnEqual 
AnnExport 
AnnFamily 
AnnForall 
AnnForallU

Unicode variant

AnnForeign 
AnnFunId

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

AnnGroup 
AnnHeader

for CType

AnnHiding 
AnnIf 
AnnImport 
AnnIn 
AnnInfix

'infix' or 'infixl' or 'infixr'

AnnInstance 
AnnLam 
AnnLarrow

'<-'

AnnLarrowU

'<-', unicode variant

AnnLet 
AnnLollyU

The unicode arrow

AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnName

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

AnnOf 
AnnOpen

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

AnnOpenB

'(|'

AnnOpenBU

'(|', unicode variant

AnnOpenC

'{'

AnnOpenE

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

AnnOpenEQ

'[|'

AnnOpenEQU

'[|', unicode variant

AnnOpenP

'('

AnnOpenS

'['

AnnOpenPH

'(#'

AnnDollar

prefix $ -- TemplateHaskell

AnnDollarDollar

prefix $$ -- TemplateHaskell

AnnPackageName 
AnnPattern 
AnnPercent

% -- for HsExplicitMult

AnnPercentOne

'%1' -- for HsLinearArrow

AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThTyQuote

double '''

AnnTilde

~

AnnType 
AnnUnit

() for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnVia

via

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

->

AnnrarrowtailU

->, unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

Instances

Instances details
Data AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnKeywordId -> Constr #

dataTypeOf :: AnnKeywordId -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnKeywordId -> SDoc #

Eq AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Ord AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

data AnnContext #

Exact print annotation for the Context data type.

Constructors

AnnContext 

Fields

Instances

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

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

toConstr :: AnnContext -> Constr #

dataTypeOf :: AnnContext -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AnnContext 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnContext -> SDoc #

ExactPrint a => ExactPrint (LocatedC a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedC a -> Entry #

setAnnotationAnchor :: LocatedC a -> Anchor -> EpAnnComments -> LocatedC a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedC a -> EP w m (LocatedC a) #

data AnchorOperation #

If tools modify the parsed source, the MovedAnchor variant can directly provide the spacing for this item relative to the previous one when printing. This allows AST fragments with a particular anchor to be freely moved, without worrying about recalculating the appropriate anchor span.

Instances

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

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

toConstr :: AnchorOperation -> Constr #

dataTypeOf :: AnchorOperation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnchorOperation 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnchorOperation 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnchorOperation -> SDoc #

Eq AnchorOperation 
Instance details

Defined in GHC.Parser.Annotation

data Anchor #

An Anchor records the base location for the start of the syntactic element holding the annotations, and is used as the point of reference for calculating delta positions for contained annotations. It is also normally used as the reference point for the spacing of the element relative to its container. If it is moved, that relationship is tracked in the anchor_op instead.

Constructors

Anchor 

Fields

Instances

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

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

toConstr :: Anchor -> Constr #

dataTypeOf :: Anchor -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup Anchor 
Instance details

Defined in GHC.Parser.Annotation

Show Anchor 
Instance details

Defined in GHC.Parser.Annotation

Outputable Anchor 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: Anchor -> SDoc #

Eq Anchor 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Ord Anchor 
Instance details

Defined in GHC.Parser.Annotation

Outputable (GenLocated Anchor EpaComment) 
Instance details

Defined in GHC.Parser.Annotation

data AddEpAnn #

Captures an annotation, storing the AnnKeywordId and its location. The parser only ever inserts EpaLocation fields with a RealSrcSpan being the original location of the annotation in the source file. The EpaLocation can also store a delta position if the AST has been modified and needs to be pretty printed again. The usual way an AddEpAnn is created is using the mj ("make jump") function, and then it can be inserted into the appropriate annotation.

Instances

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

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

toConstr :: AddEpAnn -> Constr #

dataTypeOf :: AddEpAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AddEpAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AddEpAnn -> SDoc #

Eq AddEpAnn 
Instance details

Defined in GHC.Parser.Annotation

Ord AddEpAnn 
Instance details

Defined in GHC.Parser.Annotation

widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan #

The annotations need to all come after the anchor. Make sure this is the case.

unicodeAnn :: AnnKeywordId -> AnnKeywordId #

Convert a normal annotation into its unicode equivalent one

transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #

Transfer comments and trailing items from the annotations in the first SrcSpanAnnA argument to those in the second.

setCommentsSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann #

Replace any existing comments on a SrcAnn, used for manipulating the AST prior to exact printing the changed one.

setCommentsEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a #

Replace any existing comments, used for manipulating the AST prior to exact printing the changed one.

removeCommentsA :: SrcAnn ann -> SrcAnn ann #

Remove the comments, leaving the exact print annotations payload

reLocA :: Located e -> LocatedAn ann e #

reLoc :: LocatedAn a e -> Located e #

reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e #

parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) #

Maps the ParenType to the related opening and closing AnnKeywordId. Used when actually printing the item.

noLocA :: a -> LocatedAn an a #

noAnn :: EpAnn a #

Short form for EpAnnNotUsed

na2la :: SrcSpanAnn' a -> SrcAnn ann #

Helper function (temporary) during transition of names Discards any annotations

mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b #

la2na :: SrcSpanAnn' a -> SrcSpanAnnN #

Helper function (temporary) during transition of names Discards any annotations

la2la :: LocatedAn ann1 a2 -> LocatedAn ann2 a2 #

Helper function (temporary) during transition of names Discards any annotations

l2n :: LocatedAn a1 a2 -> LocatedN a2 #

Helper function (temporary) during transition of names Discards any annotations

l2l :: SrcSpanAnn' a -> SrcAnn ann #

epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan #

Used in the parser only, extract the SrcSpan from an EpaLocation. The parser will never insert a DeltaPos, so the partial function is safe.

epAnnAnnsL :: EpAnn a -> [a] #

deltaPos :: Int -> Int -> DeltaPos #

Smart constructor for a DeltaPos. It preserves the invariant that for the DifferentLine constructor deltaLine is always > 0.

commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann #

Remove the exact print annotations payload, leaving only the anchor and comments.

addTrailingCommaToN :: SrcSpan -> EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn #

Helper function used in the parser to add a comma location to an existing annotation.

addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnList -> EpAnn AnnList #

Helper function used in the parser to add a TrailingAnn items to an existing annotation.

addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnListItem -> EpAnn AnnListItem #

Helper function used in the parser to add a TrailingAnn items to an existing annotation.

addCommentsToSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann #

Add additional comments to a SrcAnn, used for manipulating the AST prior to exact printing the changed one.

addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a #

Add additional comments, used for manipulating the AST prior to exact printing the changed one.

addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> e3 -> GenLocated (SrcAnn ann) e3 #

addCLocA :: GenLocated (SrcSpanAnn' a) e1 -> GenLocated SrcSpan e2 -> e3 -> GenLocated (SrcAnn ann) e3 #

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

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

Name OccName GHC.Types.Name

occName :: HasOccName name => name -> OccName #

ppr :: Outputable a => a -> SDoc #

Outputable / GHC.Utils.Outputable

Panic / GHC.Utils.Panic

handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a #

RdrName / GHC.Types.Name.Reader

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

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (IEWrappedName RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

SrcLoc / GHC.Types.SrcLoc

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

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource #

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

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (LocatedA a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedA a -> Entry #

setAnnotationAnchor :: LocatedA a -> Anchor -> EpAnnComments -> LocatedA a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedA a -> EP w m (LocatedA a) #

ExactPrint a => ExactPrint (LocatedC a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedC a -> Entry #

setAnnotationAnchor :: LocatedC a -> Anchor -> EpAnnComments -> LocatedC a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedC a -> EP w m (LocatedC a) #

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP CType) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP WarningTxt) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (Located a)

Bare Located elements are simply stripped off without further processing.

Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Located a -> Entry #

setAnnotationAnchor :: Located a -> Anchor -> EpAnnComments -> Located a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Located a -> EP w m (Located a) #

ExactPrint (NonEmpty (Located (HsFieldLabel GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

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

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

(ExactPrint (HsRecField' (a GhcPs) body), ExactPrint (HsRecField' (b GhcPs) body)) => ExactPrint (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Entry #

setAnnotationAnchor :: Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> Anchor -> EpAnnComments -> Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)] -> EP w m (Either [LocatedA (HsRecField' (a GhcPs) body)] [LocatedA (HsRecField' (b GhcPs) body)]) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsRecField' (AmbiguousFieldOcc GhcPs) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

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

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

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

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

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

Defined in GHC.Types.SrcLoc

type SrcSpanLess a = a Source #

combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan #

Combines two SrcSpan into one that spans at least all the characters within both spans. Returns UnhelpfulSpan if the files differ.

StringBuffer

stringToStringBuffer :: String -> StringBuffer #

Encode a String into a StringBuffer as UTF-8. The resulting buffer is automatically managed by the garbage collector.

Misc

Non-GHC stuff

type DoGenReplacement an ast a = (Data ast, Data a) => a -> (LocatedAn an ast -> Bool) -> LocatedAn an ast -> LocatedAn an ast -> StateT Bool IO (LocatedAn an ast) Source #

type ReplaceWorker a mod = (Data a, Data mod) => mod -> Parser (LocatedA a) -> Int -> Refactoring SrcSpan -> IO mod Source #