Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Refact.Compat
Contents
- ApiAnnotation / GHC.Parser.ApiAnnotation
- BasicTypes / GHC.Types.Basic
- DynFlags / GHC.Driver.Session
- ErrUtils
- FastString / GHC.Data.FastString
- HeaderInfo / GHC.Parser.Header
- HsExpr / GHC.Hs.Expr
- HsSyn / GHC.Hs
- Name OccName GHC.Types.Name
- Outputable / GHC.Utils.Outputable
- Panic / GHC.Utils.Panic
- RdrName / GHC.Types.Name.Reader
- SrcLoc / GHC.Types.SrcLoc
- StringBuffer
- Misc
- Non-GHC stuff
- GHC 9.4 stuff
Synopsis
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnCases
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- data DeltaPos
- = SameLine {
- deltaColumn :: !Int
- | DifferentLine {
- deltaLine :: !Int
- deltaColumn :: !Int
- = SameLine {
- data Fixity = Fixity SourceText Int FixityDirection
- data SourceText
- data FlagSpec flag = FlagSpec {
- flagSpecName :: String
- flagSpecFlag :: flag
- flagSpecAction :: TurnOnFlag -> DynP ()
- flagSpecGhcMode :: GhcFlagMode
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_DumpWithWays
- | 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_InfoTableMapWithFallback
- | Opt_InfoTableMapWithStack
- | 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_PrintRedundantPromotionTicks
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LocalFloatOut
- | Opt_LocalFloatOutTopLevel
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_PolymorphicSpecialisation
- | 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_CmmControlFlow
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_WorkerWrapperUnlift
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchNonexhaustiveCases
- | Opt_NumConstantFolding
- | Opt_CoreConstantFolding
- | Opt_FastPAPCalls
- | Opt_DoTagInferenceChecks
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_ProfLateInlineCcs
- | Opt_ProfLateCcs
- | Opt_ProfManualCcs
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_Ticky_Tag
- | Opt_Ticky_AP
- | Opt_CmmThreadSanitizer
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_CompactUnwind
- | Opt_Hpc
- | Opt_FamAppCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_ExposeInternalSymbols
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_ByteCodeAndObjectCode
- | 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_SuppressCoercionTypes
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressStgReps
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | Opt_SuppressCoreSizes
- | Opt_ShowErrorContext
- | 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_WriteIfSimplifiedCore
- | Opt_UseBytecodeRatherThanObjects
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_PluginTrustworthy
- | Opt_G_NoStateHack
- | Opt_G_NoOptCoercion
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- xopt_set :: DynFlags -> Extension -> DynFlags
- xopt_unset :: DynFlags -> Extension -> DynFlags
- xFlags :: [FlagSpec Extension]
- type Errors = ErrorMessages
- type ErrorMessages = Messages GhcMessage
- onError :: String -> Errors -> a
- data FastString
- mkFastString :: String -> FastString
- getOptions :: ParserOpts -> StringBuffer -> FilePath -> (Messages PsMessage, [Located String])
- data GRHS p body
- = GRHS (XCGRHS p body) [GuardLStmt p] body
- | XGRHS !(XXGRHS p body)
- data HsExpr p
- = HsVar (XVar p) (LIdP p)
- | HsUnboundVar (XUnboundVar p) RdrName
- | HsRecSel (XRecSel p) (FieldOcc p)
- | HsOverLabel (XOverLabel p) SourceText FastString
- | HsIPVar (XIPVar p) HsIPName
- | HsOverLit (XOverLitE p) (HsOverLit p)
- | HsLit (XLitE p) (HsLit p)
- | HsLam (XLam p) (MatchGroup p (LHsExpr p))
- | HsLamCase (XLamCase p) LamCaseVariant (MatchGroup p (LHsExpr p))
- | HsApp (XApp p) (LHsExpr p) (LHsExpr p)
- | HsAppType (XAppTypeE p) (LHsExpr p) !(LHsToken "@" p) (LHsWcType (NoGhcTc p))
- | OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p)
- | HsPar (XPar p) !(LHsToken "(" p) (LHsExpr p) !(LHsToken ")" p)
- | SectionL (XSectionL p) (LHsExpr p) (LHsExpr p)
- | SectionR (XSectionR p) (LHsExpr p) (LHsExpr p)
- | ExplicitTuple (XExplicitTuple p) [HsTupArg p] Boxity
- | ExplicitSum (XExplicitSum p) ConTag SumWidth (LHsExpr p)
- | 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)]
- | HsLet (XLet p) !(LHsToken "let" p) (HsLocalBinds p) !(LHsToken "in" p) (LHsExpr p)
- | HsDo (XDo p) HsDoFlavour (XRec p [ExprLStmt p])
- | ExplicitList (XExplicitList p) [LHsExpr p]
- | RecordCon {
- rcon_ext :: XRecordCon p
- rcon_con :: XRec p (ConLikeP p)
- rcon_flds :: HsRecordBinds p
- | RecordUpd {
- rupd_ext :: XRecordUpd p
- rupd_expr :: LHsExpr p
- rupd_flds :: Either [LHsRecUpdField p] [LHsRecUpdProj p]
- | HsGetField { }
- | HsProjection {
- proj_ext :: XProjection p
- proj_flds :: NonEmpty (XRec p (DotFieldOcc p))
- | ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))
- | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p)
- | HsTypedBracket (XTypedBracket p) (LHsExpr p)
- | HsUntypedBracket (XUntypedBracket p) (HsQuote p)
- | HsTypedSplice (XTypedSplice p) (LHsExpr p)
- | HsUntypedSplice (XUntypedSplice p) (HsUntypedSplice p)
- | HsProc (XProc p) (LPat p) (LHsCmdTop p)
- | HsStatic (XStatic p) (LHsExpr p)
- | HsPragE (XPragE p) (HsPragE p) (LHsExpr p)
- | XExpr !(XXExpr p)
- data HsMatchContext p
- data HsStmtContext p
- = HsDoStmt HsDoFlavour
- | PatGuard (HsMatchContext p)
- | ParStmtCtxt (HsStmtContext p)
- | TransStmtCtxt (HsStmtContext p)
- | ArrowExpr
- data Match p body
- data MatchGroup p body
- = MG { }
- | XMatchGroup !(XXMatchGroup p body)
- data StmtLR idL idR body
- = LastStmt (XLastStmt idL idR body) body (Maybe Bool) (SyntaxExpr idR)
- | BindStmt (XBindStmt idL idR body) (LPat idL) body
- | ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR))
- | 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 { }
- | RecStmt {
- recS_ext :: XRecStmt idL idR body
- recS_stmts :: XRec idR [LStmtLR idL idR body]
- recS_later_ids :: [IdP idR]
- recS_rec_ids :: [IdP idR]
- recS_bind_fn :: SyntaxExpr idR
- recS_ret_fn :: SyntaxExpr idR
- recS_mfix_fn :: SyntaxExpr idR
- | XStmtLR !(XXStmtLR idL idR body)
- data Fixity
- data DerivStrategy pass
- = StockStrategy (XStockStrategy pass)
- | AnyclassStrategy (XAnyClassStrategy pass)
- | NewtypeStrategy (XNewtypeStrategy pass)
- | ViaStrategy (XViaStrategy pass)
- data InjectivityAnn pass
- = InjectivityAnn (XCInjectivityAnn pass) (LIdP pass) [LIdP pass]
- | XInjectivityAnn !(XXInjectivityAnn pass)
- data RuleBndr pass
- = RuleBndr (XCRuleBndr pass) (LIdP pass)
- | RuleBndrSig (XRuleBndrSig pass) (LIdP pass) (HsPatSigType pass)
- | XRuleBndr !(XXRuleBndr pass)
- data FunDep pass
- type BangType pass = HsType pass
- data Match p body
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnCases
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- data AnnDecl pass
- = HsAnnotation (XHsAnnotation pass) (AnnProvenance pass) (XRec pass (HsExpr pass))
- | XAnnDecl !(XXAnnDecl pass)
- data IE pass
- = IEVar (XIEVar pass) (LIEWrappedName pass)
- | IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass)
- | IEThingAll (XIEThingAll pass) (LIEWrappedName pass)
- | IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard [LIEWrappedName pass]
- | IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)
- | IEGroup (XIEGroup pass) Int (LHsDoc pass)
- | IEDoc (XIEDoc pass) (LHsDoc pass)
- | IEDocNamed (XIEDocNamed pass) String
- | XIE !(XXIE pass)
- data HsExpr p
- = HsVar (XVar p) (LIdP p)
- | HsUnboundVar (XUnboundVar p) RdrName
- | HsRecSel (XRecSel p) (FieldOcc p)
- | HsOverLabel (XOverLabel p) SourceText FastString
- | HsIPVar (XIPVar p) HsIPName
- | HsOverLit (XOverLitE p) (HsOverLit p)
- | HsLit (XLitE p) (HsLit p)
- | HsLam (XLam p) (MatchGroup p (LHsExpr p))
- | HsLamCase (XLamCase p) LamCaseVariant (MatchGroup p (LHsExpr p))
- | HsApp (XApp p) (LHsExpr p) (LHsExpr p)
- | HsAppType (XAppTypeE p) (LHsExpr p) !(LHsToken "@" p) (LHsWcType (NoGhcTc p))
- | OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p)
- | HsPar (XPar p) !(LHsToken "(" p) (LHsExpr p) !(LHsToken ")" p)
- | SectionL (XSectionL p) (LHsExpr p) (LHsExpr p)
- | SectionR (XSectionR p) (LHsExpr p) (LHsExpr p)
- | ExplicitTuple (XExplicitTuple p) [HsTupArg p] Boxity
- | ExplicitSum (XExplicitSum p) ConTag SumWidth (LHsExpr p)
- | 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)]
- | HsLet (XLet p) !(LHsToken "let" p) (HsLocalBinds p) !(LHsToken "in" p) (LHsExpr p)
- | HsDo (XDo p) HsDoFlavour (XRec p [ExprLStmt p])
- | ExplicitList (XExplicitList p) [LHsExpr p]
- | RecordCon {
- rcon_ext :: XRecordCon p
- rcon_con :: XRec p (ConLikeP p)
- rcon_flds :: HsRecordBinds p
- | RecordUpd {
- rupd_ext :: XRecordUpd p
- rupd_expr :: LHsExpr p
- rupd_flds :: Either [LHsRecUpdField p] [LHsRecUpdProj p]
- | HsGetField { }
- | HsProjection {
- proj_ext :: XProjection p
- proj_flds :: NonEmpty (XRec p (DotFieldOcc p))
- | ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))
- | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p)
- | HsTypedBracket (XTypedBracket p) (LHsExpr p)
- | HsUntypedBracket (XUntypedBracket p) (HsQuote p)
- | HsTypedSplice (XTypedSplice p) (LHsExpr p)
- | HsUntypedSplice (XUntypedSplice p) (HsUntypedSplice p)
- | HsProc (XProc p) (LPat p) (LHsCmdTop p)
- | HsStatic (XStatic p) (LHsExpr p)
- | HsPragE (XPragE p) (HsPragE p) (LHsExpr p)
- | XExpr !(XXExpr p)
- data NoExtField = NoExtField
- data SrcUnpackedness
- data SrcStrictness
- type family NoGhcTc p
- type family XXIEWrappedName p
- type family XIEType p
- type family XIEPattern p
- type family XIEName p
- type family XXIE x
- type family XIEDocNamed x
- type family XIEDoc x
- type family XIEGroup x
- type family XIEModuleContents x
- type family XIEThingWith x
- type family XIEThingAll x
- type family XIEThingAbs x
- type family XIEVar x
- type family ImportDeclPkgQual x
- type family XXImportDecl x
- type family XCImportDecl x
- type family XXFieldOcc x
- type family XCFieldOcc x
- type family XXConDeclField x
- type family XConDeclField x
- type family XXTyVarBndr x
- type family XKindedTyVar x
- type family XUserTyVar x
- type family XXHsForAllTelescope x
- type family XHsForAllInvis x
- type family XHsForAllVis x
- type family XXTyLit x
- type family XCharTy x
- type family XStrTy x
- type family XNumTy x
- type family XXType x
- type family XWildCardTy x
- type family XTyLit x
- type family XExplicitTupleTy x
- type family XExplicitListTy x
- type family XRecTy x
- type family XBangTy x
- type family XDocTy x
- type family XSpliceTy x
- type family XKindSig x
- type family XStarTy x
- type family XIParamTy x
- type family XParTy x
- type family XOpTy x
- type family XSumTy x
- type family XTupleTy x
- type family XListTy x
- type family XFunTy x
- type family XAppKindTy x
- type family XAppTy x
- type family XTyVar x
- type family XQualTy x
- type family XForAllTy x
- type family XXHsPatSigType x
- type family XHsPS x
- type family XXHsWildCardBndrs x b
- type family XHsWC x b
- type family XXHsSigType x
- type family XHsSig x
- type family XXHsOuterTyVarBndrs x
- type family XHsOuterExplicit x flag
- type family XHsOuterImplicit x
- type family XXLHsQTyVars x
- type family XHsQTvs x
- type family XHsFieldBind x
- type family XXPat x
- type family XCoPat x
- type family XSigPat x
- type family XNPlusKPat x
- type family XNPat x
- type family XLitPat x
- type family XSplicePat x
- type family XViewPat x
- type family XConPat x
- type family XSumPat x
- type family XTuplePat x
- type family XListPat x
- type family XBangPat x
- type family XParPat x
- type family XAsPat x
- type family XLazyPat x
- type family XVarPat x
- type family XWildPat x
- type family XXOverLit x
- type family XOverLit x
- type family XXLit x
- type family XHsDoublePrim x
- type family XHsFloatPrim x
- type family XHsRat x
- type family XHsInteger x
- type family XHsWord64Prim x
- type family XHsInt64Prim x
- type family XHsWordPrim x
- type family XHsIntPrim x
- type family XHsInt x
- type family XHsStringPrim x
- type family XHsString x
- type family XHsCharPrim x
- type family XHsChar x
- type family XXApplicativeArg x
- type family XApplicativeArgMany x
- type family XApplicativeArgOne x
- type family XXParStmtBlock x x'
- type family XParStmtBlock x x'
- type family XXCmd x
- type family XCmdWrap x
- type family XCmdDo x
- type family XCmdLet x
- type family XCmdIf x
- type family XCmdLamCase x
- type family XCmdCase x
- type family XCmdPar x
- type family XCmdLam x
- type family XCmdApp x
- type family XCmdArrForm x
- type family XCmdArrApp x
- type family XXStmtLR x x' b
- type family XRecStmt x x' b
- type family XTransStmt x x' b
- type family XParStmt x x' b
- type family XLetStmt x x' b
- type family XBodyStmt x x' b
- type family XApplicativeStmt x x' b
- type family XBindStmt x x' b
- type family XLastStmt x x' b
- type family XXGRHS x b
- type family XCGRHS x b
- type family XXGRHSs x b
- type family XCGRHSs x b
- type family XXMatch x b
- type family XCMatch x b
- type family XXMatchGroup x b
- type family XMG x b
- type family XXCmdTop x
- type family XCmdTop x
- type family XXQuote x
- type family XVarBr x
- type family XTypBr x
- type family XDecBrG x
- type family XDecBrL x
- type family XPatBr x
- type family XExpBr x
- type family XXUntypedSplice x
- type family XQuasiQuote x
- type family XUntypedSpliceExpr x
- type family XXTupArg x
- type family XMissing x
- type family XPresent x
- type family XXAmbiguousFieldOcc x
- type family XAmbiguous x
- type family XUnambiguous x
- type family XXPragE x
- type family XSCC x
- type family XXDotFieldOcc x
- type family XCDotFieldOcc x
- type family XXExpr x
- type family XPragE x
- type family XBinTick x
- type family XTick x
- type family XStatic x
- type family XProc x
- type family XUntypedSplice x
- type family XTypedSplice x
- type family XUntypedBracket x
- type family XTypedBracket x
- type family XArithSeq x
- type family XExprWithTySig x
- type family XProjection x
- type family XGetField x
- type family XRecordUpd x
- type family XRecordCon x
- type family XExplicitList x
- type family XDo x
- type family XLet x
- type family XMultiIf x
- type family XIf x
- type family XCase x
- type family XExplicitSum x
- type family XExplicitTuple x
- type family XSectionR x
- type family XSectionL x
- type family XPar x
- type family XNegApp x
- type family XOpApp x
- type family XAppTypeE x
- type family XApp x
- type family XLamCase x
- type family XLam x
- type family XLitE x
- type family XOverLitE x
- type family XIPVar x
- type family XOverLabel x
- type family XRecSel x
- type family XUnboundVar x
- type family XVar x
- type family XXModule x
- type family XCModule x
- type family XXInjectivityAnn x
- type family XCInjectivityAnn x
- type family XXRoleAnnotDecl x
- type family XCRoleAnnotDecl x
- type family XXAnnDecl x
- type family XHsAnnotation x
- type family XXWarnDecl x
- type family XWarning x
- type family XXWarnDecls x
- type family XWarnings x
- type family XXRuleBndr x
- type family XRuleBndrSig x
- type family XCRuleBndr x
- type family XXRuleDecl x
- type family XHsRule x
- type family XXRuleDecls x
- type family XCRuleDecls x
- type family XXForeignExport x
- type family XCExport x
- type family XXForeignImport x
- type family XCImport x
- type family XXForeignDecl x
- type family XForeignExport x
- type family XForeignImport x
- type family XXDefaultDecl x
- type family XCDefaultDecl x
- type family XViaStrategy x
- type family XNewtypeStrategy x
- type family XAnyClassStrategy x
- type family XStockStrategy x
- type family XXDerivDecl x
- type family XCDerivDecl x
- type family XXInstDecl x
- type family XTyFamInstD x
- type family XDataFamInstD x
- type family XClsInstD x
- type family XXClsInstDecl x
- type family XCClsInstDecl x
- type family XXTyFamInstDecl x
- type family XCTyFamInstDecl x
- type family XXFamEqn x r
- type family XCFamEqn x r
- type family XXConDecl x
- type family XConDeclH98 x
- type family XConDeclGADT x
- type family XXDerivClauseTys x
- type family XDctMulti x
- type family XDctSingle x
- type family XXHsDerivingClause x
- type family XCHsDerivingClause x
- type family XXHsDataDefn x
- type family XCHsDataDefn x
- type family XXFamilyDecl x
- type family XCFamilyDecl x
- type family XXFamilyResultSig x
- type family XTyVarSig x
- type family XCKindSig x
- type family XNoSig x
- type family XXTyClGroup x
- type family XCTyClGroup x
- type family XXFunDep x
- type family XCFunDep x
- type family XXTyClDecl x
- type family XClassDecl x
- type family XDataDecl x
- type family XSynDecl x
- type family XFamDecl x
- type family XXSpliceDecl x
- type family XSpliceDecl x
- type family XXHsGroup x
- type family XCHsGroup x
- type family XXHsDecl x
- type family XRoleAnnotD x
- type family XDocD x
- type family XSpliceD x
- type family XRuleD x
- type family XAnnD x
- type family XWarningD x
- type family XForD x
- type family XDefD x
- type family XKindSigD x
- type family XSigD x
- type family XValD x
- type family XDerivD x
- type family XInstD x
- type family XTyClD x
- type family XXStandaloneKindSig x
- type family XStandaloneKindSig x
- type family XXFixitySig x
- type family XFixitySig x
- type family XXSig x
- type family XCompleteMatchSig x
- type family XSCCFunSig x
- type family XMinimalSig x
- type family XSpecInstSig x
- type family XSpecSig x
- type family XInlineSig x
- type family XFixSig x
- type family XIdSig x
- type family XClassOpSig x
- type family XPatSynSig x
- type family XTypeSig x
- type family XXIPBind x
- type family XCIPBind x
- type family XXHsIPBinds x
- type family XIPBinds x
- type family XXPatSynBind x x'
- type family XPSB x x'
- type family XXHsBindsLR x x'
- type family XPatSynBind x x'
- type family XVarBind x x'
- type family XPatBind x x'
- type family XFunBind x x'
- type family XXValBindsLR x x'
- type family XValBinds x x'
- type family XXHsLocalBindsLR x x'
- type family XEmptyLocalBinds x x'
- type family XHsIPBinds x x'
- type family XHsValBinds x x'
- type LIdP p = XRec p (IdP p)
- type family IdP p
- class WrapXRec p a where
- class MapXRec p where
- class UnXRec p where
- type family Anno a = (b :: Type)
- type family XRec p a = (r :: Type) | r -> a
- data DataConCantHappen
- newtype ModuleName = ModuleName FastString
- data IsBootInterface
- type Mult = Type
- data LayoutInfo pass
- = ExplicitBraces !(LHsToken "{" pass) !(LHsToken "}" pass)
- | VirtualBraces !Int
- | NoLayoutInfo
- data HsUniToken (tok :: Symbol) (utok :: Symbol)
- data HsToken (tok :: Symbol) = HsTok
- type LHsUniToken (tok :: Symbol) (utok :: Symbol) p = XRec p (HsUniToken tok utok)
- type LHsToken (tok :: Symbol) p = XRec p (HsToken tok)
- newtype HsDocStringChunk = HsDocStringChunk ByteString
- type LHsDocStringChunk = Located HsDocStringChunk
- data HsDocStringDecorator
- data HsDocString
- type LHsDocString = Located HsDocString
- type LPat p = XRec p (Pat p)
- type LHsExpr p = XRec p (HsExpr p)
- type family SyntaxExpr p
- data GRHSs p body
- = GRHSs {
- grhssExt :: XCGRHSs p body
- grhssGRHSs :: [LGRHS p body]
- grhssLocalBinds :: HsLocalBinds p
- | XGRHSs !(XXGRHSs p body)
- = GRHSs {
- data MatchGroup p body
- = MG { }
- | XMatchGroup !(XXMatchGroup p body)
- data HsUntypedSplice id
- = HsUntypedSpliceExpr (XUntypedSpliceExpr id) (LHsExpr id)
- | HsQuasiQuote (XQuasiQuote id) (IdP id) (XRec id FastString)
- | XUntypedSplice !(XXUntypedSplice id)
- data PromotionFlag
- data NoEpAnns = NoEpAnns
- type EpAnnCO = EpAnn NoEpAnns
- data AnnSortKey
- data AnnPragma = AnnPragma {}
- data NameAdornment
- data NameAnn
- = NameAnn { }
- | NameAnnCommas { }
- | NameAnnBars { }
- | NameAnnOnly { }
- | NameAnnRArrow { }
- | NameAnnQuote { }
- | NameAnnTrailing {
- nann_trailing :: [TrailingAnn]
- data AnnContext = AnnContext {
- ac_darrow :: Maybe (IsUnicodeSyntax, EpaLocation)
- ac_open :: [EpaLocation]
- ac_close :: [EpaLocation]
- data ParenType
- data AnnParen = AnnParen {}
- data AnnList = AnnList {}
- data AnnListItem = AnnListItem {
- lann_trailing :: [TrailingAnn]
- data TrailingAnn
- type LocatedAn an = GenLocated (SrcAnn an)
- type SrcSpanAnnC = SrcAnn AnnContext
- type SrcSpanAnnP = SrcAnn AnnPragma
- type SrcSpanAnnL = SrcAnn AnnList
- type SrcSpanAnnN = SrcAnn NameAnn
- type SrcSpanAnnA = SrcAnn AnnListItem
- type LocatedC = GenLocated SrcSpanAnnC
- type LocatedP = GenLocated SrcSpanAnnP
- type LocatedL = GenLocated SrcSpanAnnL
- type LocatedN = GenLocated SrcSpanAnnN
- type LocatedA = GenLocated SrcSpanAnnA
- type SrcAnn ann = SrcSpanAnn' (EpAnn ann)
- data SrcSpanAnn' a = SrcSpanAnn !a !SrcSpan
- type LEpaComment = GenLocated Anchor EpaComment
- data EpAnnComments
- = EpaComments {
- priorComments :: ![LEpaComment]
- | EpaCommentsBalanced {
- priorComments :: ![LEpaComment]
- followingComments :: ![LEpaComment]
- = EpaComments {
- data AnchorOperation
- data Anchor = Anchor {}
- data EpAnn ann
- = EpAnn {
- entry :: !Anchor
- anns :: !ann
- comments :: !EpAnnComments
- | EpAnnNotUsed
- = EpAnn {
- data DeltaPos
- = SameLine {
- deltaColumn :: !Int
- | DifferentLine {
- deltaLine :: !Int
- deltaColumn :: !Int
- = SameLine {
- data TokenLocation
- data EpaLocation
- = EpaSpan !RealSrcSpan !(Maybe BufSpan)
- | EpaDelta !DeltaPos ![LEpaComment]
- data AddEpAnn = AddEpAnn AnnKeywordId EpaLocation
- data EpaCommentTok
- data EpaComment = EpaComment {}
- data HasE
- data IsUnicodeSyntax
- 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)
- type family NoGhcTcPass (p :: Pass) :: Pass where ...
- type family IdGhcP (pass :: Pass) where ...
- class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass (p :: Pass) where
- type GhcTc = GhcPass 'Typechecked
- type GhcRn = GhcPass 'Renamed
- type GhcPs = GhcPass 'Parsed
- data Pass
- = Parsed
- | Renamed
- | Typechecked
- data GhcPass (c :: Pass) where
- type IsSrcSpanAnn (p :: Pass) a = (Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a), IsPass p)
- data ExtractedTHDocs = ExtractedTHDocs {
- ethd_mod_header :: Maybe (HsDoc GhcRn)
- ethd_decl_docs :: UniqMap Name (HsDoc GhcRn)
- ethd_arg_docs :: UniqMap Name (IntMap (HsDoc GhcRn))
- ethd_inst_docs :: UniqMap Name (HsDoc GhcRn)
- data Docs = Docs {}
- type DocStructure = [DocStructureItem]
- data DocStructureItem
- = DsiSectionHeading !Int !(HsDoc GhcRn)
- | DsiDocChunk !(HsDoc GhcRn)
- | DsiNamedChunkRef !String
- | DsiExports !Avails
- | DsiModExport !(NonEmpty ModuleName) !Avails
- type LHsDoc pass = Located (HsDoc pass)
- data WithHsDocIdentifiers a pass = WithHsDocIdentifiers {
- hsDocString :: !a
- hsDocIdentifiers :: ![Located (IdP pass)]
- type HsDoc = WithHsDocIdentifiers HsDocString
- type LIEWrappedName p = XRec p (IEWrappedName p)
- data IEWrappedName p
- = IEName (XIEName p) (LIdP p)
- | IEPattern (XIEPattern p) (LIdP p)
- | IEType (XIEType p) (LIdP p)
- | XIEWrappedName !(XXIEWrappedName p)
- data IEWildcard
- type LIE pass = XRec pass (IE pass)
- data ImportListInterpretation
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclName :: XRec pass ModuleName
- ideclPkgQual :: ImportDeclPkgQual pass
- ideclSource :: IsBootInterface
- ideclSafe :: Bool
- ideclQualified :: ImportDeclQualifiedStyle
- ideclAs :: Maybe (XRec pass ModuleName)
- ideclImportList :: Maybe (ImportListInterpretation, XRec pass [LIE pass])
- | XImportDecl !(XXImportDecl pass)
- = ImportDecl {
- data ImportDeclQualifiedStyle
- type LImportDecl pass = XRec pass (ImportDecl pass)
- data EpAnnImportDecl = EpAnnImportDecl {}
- data XImportDeclPass = XImportDeclPass {}
- data OverLitVal
- data HsOverLit p
- data HsLit x
- = HsChar (XHsChar x) Char
- | HsCharPrim (XHsCharPrim x) Char
- | HsString (XHsString x) FastString
- | HsStringPrim (XHsStringPrim x) !ByteString
- | HsInt (XHsInt x) IntegralLit
- | HsIntPrim (XHsIntPrim x) Integer
- | HsWordPrim (XHsWordPrim x) Integer
- | HsInt64Prim (XHsInt64Prim x) Integer
- | HsWord64Prim (XHsWord64Prim x) Integer
- | HsInteger (XHsInteger x) Integer Type
- | HsRat (XHsRat x) FractionalLit Type
- | HsFloatPrim (XHsFloatPrim x) FractionalLit
- | HsDoublePrim (XHsDoublePrim x) FractionalLit
- | XLit !(XXLit x)
- data HsImplBang
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data AmbiguousFieldOcc pass
- = Unambiguous (XUnambiguous pass) (XRec pass RdrName)
- | Ambiguous (XAmbiguous pass) (XRec pass RdrName)
- | XAmbiguousFieldOcc !(XXAmbiguousFieldOcc pass)
- type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass)
- data FieldOcc pass
- = FieldOcc {
- foExt :: XCFieldOcc pass
- foLabel :: XRec pass RdrName
- | XFieldOcc !(XXFieldOcc pass)
- = FieldOcc {
- type LFieldOcc pass = XRec pass (FieldOcc pass)
- type LHsTypeArg p = HsArg (LHsType p) (LHsKind p)
- data HsArg tm ty
- data HsConDetails tyarg arg rec
- data ConDeclField pass
- = ConDeclField {
- cd_fld_ext :: XConDeclField pass
- cd_fld_names :: [LFieldOcc pass]
- cd_fld_type :: LBangType pass
- cd_fld_doc :: Maybe (LHsDoc pass)
- | XConDeclField !(XXConDeclField pass)
- = ConDeclField {
- type LConDeclField pass = XRec pass (ConDeclField pass)
- data HsTupleSort
- data HsScaled pass a = HsScaled (HsArrow pass) a
- data HsLinearArrowTokens pass
- = HsPct1 !(LHsToken "%1" pass) !(LHsUniToken "->" "\8594" pass)
- | HsLolly !(LHsToken "\8888" pass)
- data HsArrow pass
- = HsUnrestrictedArrow !(LHsUniToken "->" "\8594" pass)
- | HsLinearArrow !(HsLinearArrowTokens pass)
- | HsExplicitMult !(LHsToken "%" pass) !(LHsType pass) !(LHsUniToken "->" "\8594" pass)
- data HsTyLit pass
- data HsType pass
- = HsForAllTy {
- hst_xforall :: XForAllTy pass
- hst_tele :: HsForAllTelescope pass
- hst_body :: LHsType pass
- | HsQualTy { }
- | 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) PromotionFlag (LHsType pass) (LIdP pass) (LHsType pass)
- | HsParTy (XParTy pass) (LHsType pass)
- | HsIParamTy (XIParamTy pass) (XRec pass HsIPName) (LHsType pass)
- | HsStarTy (XStarTy pass) Bool
- | HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
- | HsSpliceTy (XSpliceTy pass) (HsUntypedSplice pass)
- | HsDocTy (XDocTy pass) (LHsType pass) (LHsDoc pass)
- | 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 pass)
- | HsWildCardTy (XWildCardTy pass)
- | XHsType !(XXType pass)
- = HsForAllTy {
- data HsTyVarBndr flag pass
- = UserTyVar (XUserTyVar pass) flag (LIdP pass)
- | KindedTyVar (XKindedTyVar pass) flag (LIdP pass) (LHsKind pass)
- | XTyVarBndr !(XXTyVarBndr pass)
- newtype HsIPName = HsIPName FastString
- data HsSigType pass
- = HsSig { }
- | XHsSigType !(XXHsSigType pass)
- type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
- type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
- type LHsSigType pass = XRec pass (HsSigType pass)
- data HsPatSigType pass
- = HsPS { }
- | XHsPatSigType !(XXHsPatSigType pass)
- data HsWildCardBndrs pass thing
- = HsWC { }
- | XHsWildCardBndrs !(XXHsWildCardBndrs pass thing)
- type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs ()
- type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity
- data HsOuterTyVarBndrs flag pass
- = HsOuterImplicit {
- hso_ximplicit :: XHsOuterImplicit pass
- | HsOuterExplicit {
- hso_xexplicit :: XHsOuterExplicit pass flag
- hso_bndrs :: [LHsTyVarBndr flag (NoGhcTc pass)]
- | XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass)
- = HsOuterImplicit {
- data LHsQTyVars pass
- = HsQTvs {
- hsq_ext :: XHsQTvs pass
- hsq_explicit :: [LHsTyVarBndr () pass]
- | XLHsQTyVars !(XXLHsQTyVars pass)
- = HsQTvs {
- type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass)
- data HsForAllTelescope pass
- = HsForAllVis {
- hsf_xvis :: XHsForAllVis pass
- hsf_vis_bndrs :: [LHsTyVarBndr () pass]
- | HsForAllInvis {
- hsf_xinvis :: XHsForAllInvis pass
- hsf_invis_bndrs :: [LHsTyVarBndr Specificity pass]
- | XHsForAllTelescope !(XXHsForAllTelescope pass)
- = HsForAllVis {
- type LHsKind pass = XRec pass (HsKind pass)
- type HsKind pass = HsType pass
- type LHsType pass = XRec pass (HsType pass)
- type HsContext pass = [LHsType pass]
- type LHsContext pass = XRec pass (HsContext pass)
- type LBangType pass = XRec pass (BangType pass)
- data HsFieldBind lhs rhs = HsFieldBind {}
- type HsRecUpdField p = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr p)
- type HsRecField p arg = HsFieldBind (LFieldOcc p) arg
- type LHsRecUpdField p = XRec p (HsRecUpdField p)
- type LHsRecField p arg = XRec p (HsRecField p arg)
- type LHsFieldBind p id arg = XRec p (HsFieldBind id arg)
- newtype RecFieldsDotDot = RecFieldsDotDot {}
- data HsRecFields p arg = HsRecFields {
- rec_flds :: [LHsRecField p arg]
- rec_dotdot :: Maybe (XRec p RecFieldsDotDot)
- type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) (LPat p) (HsRecFields p (LPat p))
- data HsConPatTyArg p = HsConPatTyArg !(LHsToken "@" p) (HsPatSigType p)
- type family ConLikeP x
- data HsPatSynDir id
- data RecordPatSynField pass = RecordPatSynField {
- recordPatSynField :: FieldOcc pass
- recordPatSynPatVar :: LIdP pass
- type HsPatSynDetails pass = HsConDetails Void (LIdP pass) [RecordPatSynField pass]
- data FixitySig pass
- = FixitySig (XFixitySig pass) [LIdP pass] Fixity
- | XFixitySig !(XXFixitySig pass)
- type LFixitySig pass = XRec pass (FixitySig pass)
- data Sig pass
- = TypeSig (XTypeSig pass) [LIdP pass] (LHsSigWcType pass)
- | PatSynSig (XPatSynSig pass) [LIdP pass] (LHsSigType pass)
- | ClassOpSig (XClassOpSig pass) Bool [LIdP pass] (LHsSigType pass)
- | FixSig (XFixSig pass) (FixitySig pass)
- | InlineSig (XInlineSig pass) (LIdP pass) InlinePragma
- | SpecSig (XSpecSig pass) (LIdP pass) [LHsSigType pass] InlinePragma
- | SpecInstSig (XSpecInstSig pass) (LHsSigType pass)
- | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
- | SCCFunSig (XSCCFunSig pass) (LIdP pass) (Maybe (XRec pass StringLiteral))
- | CompleteMatchSig (XCompleteMatchSig pass) (XRec pass [LIdP pass]) (Maybe (LIdP pass))
- | XSig !(XXSig pass)
- type LSig pass = XRec pass (Sig pass)
- data IPBind id
- type LIPBind id = XRec id (IPBind id)
- data HsIPBinds id
- = IPBinds (XIPBinds id) [LIPBind id]
- | XHsIPBinds !(XXHsIPBinds id)
- data PatSynBind idL idR
- = PSB {
- psb_ext :: XPSB idL idR
- psb_id :: LIdP idL
- psb_args :: HsPatSynDetails idR
- psb_def :: LPat idR
- psb_dir :: HsPatSynDir idR
- | XPatSynBind !(XXPatSynBind idL idR)
- = PSB {
- data HsBindLR idL idR
- = FunBind {
- fun_ext :: XFunBind idL idR
- fun_id :: LIdP idL
- fun_matches :: MatchGroup idR (LHsExpr idR)
- | PatBind { }
- | VarBind { }
- | PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR)
- | XHsBindsLR !(XXHsBindsLR idL idR)
- = FunBind {
- type LHsBindLR idL idR = XRec idL (HsBindLR idL idR)
- type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
- type HsBind id = HsBindLR id id
- type LHsBinds id = LHsBindsLR id id
- type LHsBind id = LHsBindLR id id
- data HsValBindsLR idL idR
- = ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR]
- | XValBindsLR !(XXValBindsLR idL idR)
- type HsValBinds id = HsValBindsLR id id
- type LHsLocalBindsLR idL idR = XRec idL (HsLocalBindsLR idL idR)
- data HsLocalBindsLR idL idR
- = HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR)
- | HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR)
- | EmptyLocalBinds (XEmptyLocalBinds idL idR)
- | XHsLocalBindsLR !(XXHsLocalBindsLR idL idR)
- type LHsLocalBinds id = XRec id (HsLocalBinds id)
- type HsLocalBinds id = HsLocalBindsLR id id
- data RoleAnnotDecl pass
- = RoleAnnotDecl (XCRoleAnnotDecl pass) (LIdP pass) [XRec pass (Maybe Role)]
- | XRoleAnnotDecl !(XXRoleAnnotDecl pass)
- type LRoleAnnotDecl pass = XRec pass (RoleAnnotDecl pass)
- data AnnProvenance pass
- = ValueAnnProvenance (LIdP pass)
- | TypeAnnProvenance (LIdP pass)
- | ModuleAnnProvenance
- type LAnnDecl pass = XRec pass (AnnDecl pass)
- data WarnDecl pass
- = Warning (XWarning pass) [LIdP pass] (WarningTxt pass)
- | XWarnDecl !(XXWarnDecl pass)
- type LWarnDecl pass = XRec pass (WarnDecl pass)
- data WarnDecls pass
- = Warnings {
- wd_ext :: XWarnings pass
- wd_warnings :: [LWarnDecl pass]
- | XWarnDecls !(XXWarnDecls pass)
- = Warnings {
- type LWarnDecls pass = XRec pass (WarnDecls pass)
- data DocDecl pass
- = DocCommentNext (LHsDoc pass)
- | DocCommentPrev (LHsDoc pass)
- | DocCommentNamed String (LHsDoc pass)
- | DocGroup Int (LHsDoc pass)
- type LDocDecl pass = XRec pass (DocDecl pass)
- type LRuleBndr pass = XRec pass (RuleBndr pass)
- data RuleDecl pass
- type LRuleDecl pass = XRec pass (RuleDecl pass)
- data RuleDecls pass
- = HsRules {
- rds_ext :: XCRuleDecls pass
- rds_rules :: [LRuleDecl pass]
- | XRuleDecls !(XXRuleDecls pass)
- = HsRules {
- type LRuleDecls pass = XRec pass (RuleDecls pass)
- data ForeignExport pass
- = CExport (XCExport pass) (XRec pass CExportSpec)
- | XForeignExport !(XXForeignExport pass)
- data CImportSpec
- data ForeignImport pass
- = CImport (XCImport pass) (XRec pass CCallConv) (XRec pass Safety) (Maybe Header) CImportSpec
- | XForeignImport !(XXForeignImport pass)
- data ForeignDecl pass
- = ForeignImport {
- fd_i_ext :: XForeignImport pass
- fd_name :: LIdP pass
- fd_sig_ty :: LHsSigType pass
- fd_fi :: ForeignImport pass
- | ForeignExport {
- fd_e_ext :: XForeignExport pass
- fd_name :: LIdP pass
- fd_sig_ty :: LHsSigType pass
- fd_fe :: ForeignExport pass
- | XForeignDecl !(XXForeignDecl pass)
- = ForeignImport {
- type LForeignDecl pass = XRec pass (ForeignDecl pass)
- data DefaultDecl pass
- = DefaultDecl (XCDefaultDecl pass) [LHsType pass]
- | XDefaultDecl !(XXDefaultDecl pass)
- type LDefaultDecl pass = XRec pass (DefaultDecl pass)
- type LDerivStrategy pass = XRec pass (DerivStrategy pass)
- data DerivDecl pass
- = DerivDecl {
- deriv_ext :: XCDerivDecl pass
- deriv_type :: LHsSigWcType pass
- deriv_strategy :: Maybe (LDerivStrategy pass)
- deriv_overlap_mode :: Maybe (XRec pass OverlapMode)
- | XDerivDecl !(XXDerivDecl pass)
- = DerivDecl {
- type LDerivDecl pass = XRec pass (DerivDecl pass)
- data InstDecl pass
- = ClsInstD {
- cid_d_ext :: XClsInstD pass
- cid_inst :: ClsInstDecl pass
- | DataFamInstD {
- dfid_ext :: XDataFamInstD pass
- dfid_inst :: DataFamInstDecl pass
- | TyFamInstD {
- tfid_ext :: XTyFamInstD pass
- tfid_inst :: TyFamInstDecl pass
- | XInstDecl !(XXInstDecl pass)
- = ClsInstD {
- type LInstDecl pass = XRec pass (InstDecl pass)
- data ClsInstDecl pass
- = ClsInstDecl {
- cid_ext :: XCClsInstDecl pass
- cid_poly_ty :: LHsSigType pass
- cid_binds :: LHsBinds pass
- cid_sigs :: [LSig pass]
- cid_tyfam_insts :: [LTyFamInstDecl pass]
- cid_datafam_insts :: [LDataFamInstDecl pass]
- cid_overlap_mode :: Maybe (XRec pass OverlapMode)
- | XClsInstDecl !(XXClsInstDecl pass)
- = ClsInstDecl {
- type LClsInstDecl pass = XRec pass (ClsInstDecl pass)
- data FamEqn pass rhs
- = FamEqn {
- feqn_ext :: XCFamEqn pass rhs
- feqn_tycon :: LIdP pass
- feqn_bndrs :: HsOuterFamEqnTyVarBndrs pass
- feqn_pats :: HsTyPats pass
- feqn_fixity :: LexicalFixity
- feqn_rhs :: rhs
- | XFamEqn !(XXFamEqn pass rhs)
- = FamEqn {
- newtype DataFamInstDecl pass = DataFamInstDecl {
- dfid_eqn :: FamEqn pass (HsDataDefn pass)
- type LDataFamInstDecl pass = XRec pass (DataFamInstDecl pass)
- data TyFamInstDecl pass
- = TyFamInstDecl {
- tfid_xtn :: XCTyFamInstDecl pass
- tfid_eqn :: TyFamInstEqn pass
- | XTyFamInstDecl !(XXTyFamInstDecl pass)
- = TyFamInstDecl {
- type LTyFamInstDecl pass = XRec pass (TyFamInstDecl pass)
- type LTyFamDefltDecl pass = XRec pass (TyFamDefltDecl pass)
- type TyFamDefltDecl = TyFamInstDecl
- type TyFamInstEqn pass = FamEqn pass (LHsType pass)
- type HsTyPats pass = [LHsTypeArg pass]
- type LTyFamInstEqn pass = XRec pass (TyFamInstEqn pass)
- data HsConDeclGADTDetails pass
- = PrefixConGADT [HsScaled pass (LBangType pass)]
- | RecConGADT (XRec pass [LConDeclField pass]) (LHsUniToken "->" "\8594" pass)
- type HsConDeclH98Details pass = HsConDetails Void (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass])
- data ConDecl pass
- = ConDeclGADT {
- con_g_ext :: XConDeclGADT pass
- con_names :: NonEmpty (LIdP pass)
- con_dcolon :: !(LHsUniToken "::" "\8759" pass)
- con_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
- con_mb_cxt :: Maybe (LHsContext pass)
- con_g_args :: HsConDeclGADTDetails pass
- con_res_ty :: LHsType pass
- con_doc :: Maybe (LHsDoc pass)
- | ConDeclH98 {
- con_ext :: XConDeclH98 pass
- con_name :: LIdP pass
- con_forall :: Bool
- con_ex_tvs :: [LHsTyVarBndr Specificity pass]
- con_mb_cxt :: Maybe (LHsContext pass)
- con_args :: HsConDeclH98Details pass
- con_doc :: Maybe (LHsDoc pass)
- | XConDecl !(XXConDecl pass)
- = ConDeclGADT {
- type LConDecl pass = XRec pass (ConDecl pass)
- data DataDefnCons a
- = NewTypeCon a
- | DataTypeCons Bool [a]
- data NewOrData
- data StandaloneKindSig pass
- = StandaloneKindSig (XStandaloneKindSig pass) (LIdP pass) (LHsSigType pass)
- | XStandaloneKindSig !(XXStandaloneKindSig pass)
- type LStandaloneKindSig pass = XRec pass (StandaloneKindSig pass)
- data DerivClauseTys pass
- = DctSingle (XDctSingle pass) (LHsSigType pass)
- | DctMulti (XDctMulti pass) [LHsSigType pass]
- | XDerivClauseTys !(XXDerivClauseTys pass)
- type LDerivClauseTys pass = XRec pass (DerivClauseTys pass)
- data HsDerivingClause pass
- = HsDerivingClause {
- deriv_clause_ext :: XCHsDerivingClause pass
- deriv_clause_strategy :: Maybe (LDerivStrategy pass)
- deriv_clause_tys :: LDerivClauseTys pass
- | XHsDerivingClause !(XXHsDerivingClause pass)
- = HsDerivingClause {
- type LHsDerivingClause pass = XRec pass (HsDerivingClause pass)
- type HsDeriving pass = [LHsDerivingClause pass]
- data HsDataDefn pass
- = HsDataDefn {
- dd_ext :: XCHsDataDefn pass
- dd_ctxt :: Maybe (LHsContext pass)
- dd_cType :: Maybe (XRec pass CType)
- dd_kindSig :: Maybe (LHsKind pass)
- dd_cons :: DataDefnCons (LConDecl pass)
- dd_derivs :: HsDeriving pass
- | XHsDataDefn !(XXHsDataDefn pass)
- = HsDataDefn {
- data FamilyInfo pass
- = DataFamily
- | OpenTypeFamily
- | ClosedTypeFamily (Maybe [LTyFamInstEqn pass])
- type LInjectivityAnn pass = XRec pass (InjectivityAnn pass)
- data FamilyDecl pass
- = FamilyDecl {
- fdExt :: XCFamilyDecl pass
- fdInfo :: FamilyInfo pass
- fdTopLevel :: TopLevelFlag
- fdLName :: LIdP pass
- fdTyVars :: LHsQTyVars pass
- fdFixity :: LexicalFixity
- fdResultSig :: LFamilyResultSig pass
- fdInjectivityAnn :: Maybe (LInjectivityAnn pass)
- | XFamilyDecl !(XXFamilyDecl pass)
- = FamilyDecl {
- type LFamilyDecl pass = XRec pass (FamilyDecl pass)
- data FamilyResultSig pass
- = NoSig (XNoSig pass)
- | KindSig (XCKindSig pass) (LHsKind pass)
- | TyVarSig (XTyVarSig pass) (LHsTyVarBndr () pass)
- | XFamilyResultSig !(XXFamilyResultSig pass)
- type LFamilyResultSig pass = XRec pass (FamilyResultSig pass)
- data TyClGroup pass
- = TyClGroup {
- group_ext :: XCTyClGroup pass
- group_tyclds :: [LTyClDecl pass]
- group_roles :: [LRoleAnnotDecl pass]
- group_kisigs :: [LStandaloneKindSig pass]
- group_instds :: [LInstDecl pass]
- | XTyClGroup !(XXTyClGroup pass)
- = TyClGroup {
- type LHsFunDep pass = XRec pass (FunDep pass)
- data TyClDecl pass
- = FamDecl {
- tcdFExt :: XFamDecl pass
- tcdFam :: FamilyDecl pass
- | SynDecl {
- tcdSExt :: XSynDecl pass
- tcdLName :: LIdP pass
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdRhs :: LHsType pass
- | DataDecl {
- tcdDExt :: XDataDecl pass
- tcdLName :: LIdP pass
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdDataDefn :: HsDataDefn pass
- | ClassDecl {
- tcdCExt :: XClassDecl pass
- tcdLayout :: !(LayoutInfo pass)
- tcdCtxt :: Maybe (LHsContext pass)
- tcdLName :: LIdP pass
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdFDs :: [LHsFunDep pass]
- tcdSigs :: [LSig pass]
- tcdMeths :: LHsBinds pass
- tcdATs :: [LFamilyDecl pass]
- tcdATDefs :: [LTyFamDefltDecl pass]
- tcdDocs :: [LDocDecl pass]
- | XTyClDecl !(XXTyClDecl pass)
- = FamDecl {
- type LTyClDecl pass = XRec pass (TyClDecl pass)
- data SpliceDecoration
- data SpliceDecl p
- = SpliceDecl (XSpliceDecl p) (XRec p (HsUntypedSplice p)) SpliceDecoration
- | XSpliceDecl !(XXSpliceDecl p)
- type LSpliceDecl pass = XRec pass (SpliceDecl pass)
- data HsGroup p
- = HsGroup {
- hs_ext :: XCHsGroup p
- hs_valds :: HsValBinds p
- hs_splcds :: [LSpliceDecl p]
- hs_tyclds :: [TyClGroup p]
- hs_derivds :: [LDerivDecl p]
- hs_fixds :: [LFixitySig p]
- hs_defds :: [LDefaultDecl p]
- hs_fords :: [LForeignDecl p]
- hs_warnds :: [LWarnDecls p]
- hs_annds :: [LAnnDecl p]
- hs_ruleds :: [LRuleDecls p]
- hs_docs :: [LDocDecl p]
- | XHsGroup !(XXHsGroup p)
- = HsGroup {
- data HsDecl p
- = TyClD (XTyClD p) (TyClDecl p)
- | InstD (XInstD p) (InstDecl p)
- | DerivD (XDerivD p) (DerivDecl p)
- | ValD (XValD p) (HsBind p)
- | SigD (XSigD p) (Sig p)
- | KindSigD (XKindSigD p) (StandaloneKindSig p)
- | DefD (XDefD p) (DefaultDecl p)
- | ForD (XForD p) (ForeignDecl p)
- | WarningD (XWarningD p) (WarnDecls p)
- | AnnD (XAnnD p) (AnnDecl p)
- | RuleD (XRuleD p) (RuleDecls p)
- | SpliceD (XSpliceD p) (SpliceDecl p)
- | DocD (XDocD p) (DocDecl p)
- | RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p)
- | XHsDecl !(XXHsDecl p)
- type LHsDecl p = XRec p (HsDecl p)
- data HsDoFlavour
- = DoExpr (Maybe ModuleName)
- | MDoExpr (Maybe ModuleName)
- | GhciStmtCtxt
- | ListComp
- | MonadComp
- data HsArrowMatchContext
- data HsStmtContext p
- = HsDoStmt HsDoFlavour
- | PatGuard (HsMatchContext p)
- | ParStmtCtxt (HsStmtContext p)
- | TransStmtCtxt (HsStmtContext p)
- | ArrowExpr
- data HsMatchContext p
- data ArithSeqInfo id
- data HsQuote p
- data ApplicativeArg idL
- = ApplicativeArgOne {
- xarg_app_arg_one :: XApplicativeArgOne idL
- app_arg_pattern :: LPat idL
- arg_expr :: LHsExpr idL
- is_body_stmt :: Bool
- | ApplicativeArgMany {
- xarg_app_arg_many :: XApplicativeArgMany idL
- app_stmts :: [ExprLStmt idL]
- final_expr :: HsExpr idL
- bv_pattern :: LPat idL
- stmt_context :: HsDoFlavour
- | XApplicativeArg !(XXApplicativeArg idL)
- = ApplicativeArgOne {
- type FailOperator id = Maybe (SyntaxExpr id)
- data ParStmtBlock idL idR
- = ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR)
- | XParStmtBlock !(XXParStmtBlock idL idR)
- data TransForm
- data StmtLR idL idR body
- = LastStmt (XLastStmt idL idR body) body (Maybe Bool) (SyntaxExpr idR)
- | BindStmt (XBindStmt idL idR body) (LPat idL) body
- | ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR))
- | 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 { }
- | RecStmt {
- recS_ext :: XRecStmt idL idR body
- recS_stmts :: XRec idR [LStmtLR idL idR body]
- recS_later_ids :: [IdP idR]
- recS_rec_ids :: [IdP idR]
- recS_bind_fn :: SyntaxExpr idR
- recS_ret_fn :: SyntaxExpr idR
- recS_mfix_fn :: SyntaxExpr idR
- | XStmtLR !(XXStmtLR idL idR body)
- type GhciStmt id = Stmt id (LHsExpr id)
- type GhciLStmt id = LStmt id (LHsExpr id)
- type GuardStmt id = Stmt id (LHsExpr id)
- type GuardLStmt id = LStmt id (LHsExpr id)
- type ExprStmt id = Stmt id (LHsExpr id)
- type ExprLStmt id = LStmt id (LHsExpr id)
- type CmdStmt id = Stmt id (LHsCmd id)
- type CmdLStmt id = LStmt id (LHsCmd id)
- type LStmtLR idL idR body = XRec idL (StmtLR idL idR body)
- type LStmt id body = XRec id (StmtLR id id body)
- data GRHS p body
- = GRHS (XCGRHS p body) [GuardLStmt p] body
- | XGRHS !(XXGRHS p body)
- type LGRHS id body = XRec id (GRHS id body)
- type LMatch id body = XRec id (Match id body)
- type HsRecordBinds p = HsRecFields p (LHsExpr p)
- data HsCmdTop p
- type LHsCmdTop p = XRec p (HsCmdTop p)
- data HsArrAppType
- data HsCmd id
- = HsCmdArrApp (XCmdArrApp id) (LHsExpr id) (LHsExpr id) HsArrAppType Bool
- | HsCmdArrForm (XCmdArrForm id) (LHsExpr id) LexicalFixity (Maybe Fixity) [LHsCmdTop id]
- | HsCmdApp (XCmdApp id) (LHsCmd id) (LHsExpr id)
- | HsCmdLam (XCmdLam id) (MatchGroup id (LHsCmd id))
- | HsCmdPar (XCmdPar id) !(LHsToken "(" id) (LHsCmd id) !(LHsToken ")" id)
- | HsCmdCase (XCmdCase id) (LHsExpr id) (MatchGroup id (LHsCmd id))
- | HsCmdLamCase (XCmdLamCase id) LamCaseVariant (MatchGroup id (LHsCmd id))
- | HsCmdIf (XCmdIf id) (SyntaxExpr id) (LHsExpr id) (LHsCmd id) (LHsCmd id)
- | HsCmdLet (XCmdLet id) !(LHsToken "let" id) (HsLocalBinds id) !(LHsToken "in" id) (LHsCmd id)
- | HsCmdDo (XCmdDo id) (XRec id [CmdLStmt id])
- | XCmd !(XXCmd id)
- type LHsCmd id = XRec id (HsCmd id)
- data LamCaseVariant
- data HsTupArg id
- type LHsTupArg id = XRec id (HsTupArg id)
- data HsPragE p
- = HsPragSCC (XSCC p) StringLiteral
- | XHsPragE !(XXPragE p)
- data DotFieldOcc p
- = DotFieldOcc {
- dfoExt :: XCDotFieldOcc p
- dfoLabel :: XRec p FieldLabelString
- | XDotFieldOcc !(XXDotFieldOcc p)
- = DotFieldOcc {
- type LHsRecUpdProj p = XRec p (RecUpdProj p)
- type RecUpdProj p = RecProj p (LHsExpr p)
- type LHsRecProj p arg = XRec p (RecProj p arg)
- type RecProj p arg = HsFieldBind (LFieldLabelStrings p) arg
- newtype FieldLabelStrings p = FieldLabelStrings [XRec p (DotFieldOcc p)]
- type LFieldLabelStrings p = XRec p (FieldLabelStrings p)
- data HsUntypedSpliceResult thing
- newtype ThModFinalizers = ThModFinalizers [ForeignRef (Q ())]
- type SplicePointName = Name
- data HsModule p
- = HsModule {
- hsmodExt :: XCModule p
- hsmodName :: Maybe (XRec p ModuleName)
- hsmodExports :: Maybe (XRec p [LIE p])
- hsmodImports :: [LImportDecl p]
- hsmodDecls :: [LHsDecl p]
- | XModule !(XXModule p)
- = HsModule {
- class OutputableBndrFlag flag (p :: Pass)
- type HsCoreTy = Type
- data HsPSRn = HsPSRn {
- hsps_nwcs :: [Name]
- hsps_imp_tvs :: [Name]
- type EpAnnForallTy = EpAnn (AddEpAnn, AddEpAnn)
- data OverLitTc = OverLitTc {
- ol_rebindable :: Bool
- ol_witness :: HsExpr GhcTc
- ol_type :: Type
- data OverLitRn = OverLitRn {}
- data TcSpecPrag = SpecPrag Id HsWrapper InlinePragma
- type LTcSpecPrag = Located TcSpecPrag
- data TcSpecPrags
- data AnnSig = AnnSig {}
- newtype IdSig = IdSig {}
- data ABExport = ABE {}
- data AbsBinds = AbsBinds {
- abs_tvs :: [TyVar]
- abs_ev_vars :: [EvVar]
- abs_exports :: [ABExport]
- abs_ev_binds :: [TcEvBinds]
- abs_binds :: LHsBinds GhcTc
- abs_sig :: Bool
- data NHsValBindsLR idL = NValBinds [(RecFlag, LHsBinds idL)] [LSig GhcRn]
- data ConPatTc = ConPatTc {}
- data HsPatExpansion a b = HsPatExpanded a b
- data XXPatGhcTc
- data EpAnnSumPat = EpAnnSumPat {}
- data HsRuleAnn = HsRuleAnn {}
- data HsRuleRn = HsRuleRn NameSet NameSet
- data XViaStrategyPs = XViaStrategyPs (EpAnn [AddEpAnn]) (LHsSigType GhcPs)
- data DataDeclRn = DataDeclRn {
- tcdDataCusk :: Bool
- tcdFVs :: NameSet
- data PendingTcSplice = PendingTcSplice SplicePointName (LHsExpr GhcTc)
- data PendingRnSplice = PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn)
- data UntypedSpliceFlavour
- data DelayedSplice = DelayedSplice TcLclEnv (LHsExpr GhcRn) TcType (LHsExpr GhcTc)
- data XBindStmtTc = XBindStmtTc {}
- data XBindStmtRn = XBindStmtRn {}
- data RecStmtTc = RecStmtTc {
- recS_bind_ty :: Type
- recS_later_rets :: [PostTcExpr]
- recS_rec_rets :: [PostTcExpr]
- recS_ret_ty :: Type
- data GrhsAnn = GrhsAnn {}
- data MatchGroupTc = MatchGroupTc {}
- data CmdTopTc = CmdTopTc Type Type (CmdSyntaxTable GhcTc)
- type CmdSyntaxTable p = [(Name, HsExpr p)]
- data HsExpansion orig expanded = HsExpanded orig expanded
- data XXExprGhcTc
- data AnnsIf = AnnsIf {}
- data AnnProjection = AnnProjection {}
- data AnnFieldLabel = AnnFieldLabel {}
- data AnnExplicitSum = AnnExplicitSum {}
- data EpAnnUnboundVar = EpAnnUnboundVar {}
- data EpAnnHsCase = EpAnnHsCase {}
- data HsBracketTc = HsBracketTc {}
- data HsWrap (hs_syn :: Type -> Type) = HsWrap HsWrapper (hs_syn GhcTc)
- data SyntaxExprTc
- = SyntaxExprTc { }
- | NoSyntaxExprTc
- data SyntaxExprRn
- type family SyntaxExprGhc (p :: Pass) = (r :: Type) | r -> p where ...
- type PostTcTable = [(Name, PostTcExpr)]
- type PostTcExpr = HsExpr GhcTc
- class UnXRec p => CollectPass p where
- collectXXPat :: CollectFlag p -> XXPat p -> [IdP p] -> [IdP p]
- collectXXHsBindsLR :: XXHsBindsLR p pR -> [IdP p] -> [IdP p]
- collectXSplicePat :: CollectFlag p -> XSplicePat p -> [IdP p] -> [IdP p]
- data CollectFlag p where
- CollNoDictBinders :: forall p. CollectFlag p
- CollWithDictBinders :: CollectFlag (GhcPass 'Typechecked)
- data HsParsedModule = HsParsedModule {
- hpm_module :: Located (HsModule GhcPs)
- hpm_src_files :: [FilePath]
- data AnnsModule = AnnsModule {}
- data XModulePs = XModulePs {}
- pattern WildPat :: XWildPat p -> Pat p
- pattern VarPat :: XVarPat p -> LIdP p -> Pat p
- pattern LazyPat :: XLazyPat p -> LPat p -> Pat p
- pattern AsPat :: XAsPat p -> LIdP p -> !(LHsToken "@" p) -> LPat p -> Pat p
- pattern ParPat :: XParPat p -> !(LHsToken "(" p) -> LPat p -> !(LHsToken ")" p) -> Pat p
- pattern BangPat :: XBangPat p -> LPat p -> Pat p
- pattern ListPat :: XListPat p -> [LPat p] -> Pat p
- pattern TuplePat :: XTuplePat p -> [LPat p] -> Boxity -> Pat p
- pattern SumPat :: XSumPat p -> LPat p -> ConTag -> SumWidth -> Pat p
- pattern ConPat :: XConPat p -> XRec p (ConLikeP p) -> HsConPatDetails p -> Pat p
- pattern ViewPat :: XViewPat p -> LHsExpr p -> LPat p -> Pat p
- pattern SplicePat :: XSplicePat p -> HsUntypedSplice p -> Pat p
- pattern LitPat :: XLitPat p -> HsLit p -> Pat p
- pattern NPat :: XNPat p -> XRec p (HsOverLit p) -> Maybe (SyntaxExpr p) -> SyntaxExpr p -> Pat p
- pattern NPlusKPat :: XNPlusKPat p -> LIdP p -> XRec p (HsOverLit p) -> HsOverLit p -> SyntaxExpr p -> SyntaxExpr p -> Pat p
- pattern SigPat :: XSigPat p -> LPat p -> HsPatSigType (NoGhcTc p) -> Pat p
- pattern XPat :: !(XXPat p) -> Pat p
- pat_con_ext :: Pat p -> XConPat p
- pat_con :: Pat p -> XRec p (ConLikeP p)
- pat_args :: Pat p -> HsConPatDetails p
- noExtField :: NoExtField
- dataConCantHappen :: DataConCantHappen -> a
- stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
- moduleNameFS :: ModuleName -> FastString
- moduleNameString :: ModuleName -> String
- mkModuleName :: String -> ModuleName
- mkModuleNameFS :: FastString -> ModuleName
- moduleNameSlashes :: ModuleName -> String
- moduleNameColons :: ModuleName -> String
- pprWithDocString :: HsDocString -> SDoc -> SDoc
- mkHsDocStringChunk :: String -> HsDocStringChunk
- mkHsDocStringChunkUtf8ByteString :: ByteString -> HsDocStringChunk
- unpackHDSC :: HsDocStringChunk -> String
- mkGeneratedHsDocString :: String -> HsDocString
- isEmptyDocString :: HsDocString -> Bool
- docStringChunks :: HsDocString -> [LHsDocStringChunk]
- pprHsDocString :: HsDocString -> SDoc
- pprHsDocStrings :: [HsDocString] -> SDoc
- exactPrintHsDocString :: HsDocString -> String
- renderHsDocString :: HsDocString -> String
- renderHsDocStrings :: [HsDocString] -> String
- isPromoted :: PromotionFlag -> Bool
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- deltaPos :: Int -> Int -> DeltaPos
- getDeltaLine :: DeltaPos -> Int
- epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
- epaLocationFromSrcAnn :: SrcAnn ann -> EpaLocation
- spanAsAnchor :: SrcSpan -> Anchor
- realSpanAsAnchor :: RealSrcSpan -> Anchor
- emptyComments :: EpAnnComments
- parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId)
- trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn
- addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnList -> EpAnn AnnList
- addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnListItem -> EpAnn AnnListItem
- addTrailingCommaToN :: SrcSpan -> EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn
- l2n :: LocatedAn a1 a2 -> LocatedN a2
- n2l :: LocatedN a -> LocatedA a
- la2na :: SrcSpanAnn' a -> SrcSpanAnnN
- la2la :: LocatedAn ann1 a2 -> LocatedAn ann2 a2
- l2l :: SrcSpanAnn' a -> SrcAnn ann
- na2la :: SrcSpanAnn' a -> SrcAnn ann
- reLoc :: LocatedAn a e -> Located e
- reLocA :: Located e -> LocatedAn ann e
- reLocL :: LocatedN e -> LocatedA e
- reLocC :: LocatedN e -> LocatedC e
- reLocN :: LocatedN a -> Located a
- realSrcSpan :: SrcSpan -> RealSrcSpan
- srcSpan2e :: SrcSpan -> EpaLocation
- la2e :: SrcSpanAnn' a -> EpaLocation
- extraToAnnList :: AnnList -> [AddEpAnn] -> AnnList
- reAnn :: [TrailingAnn] -> EpAnnComments -> Located a -> LocatedA a
- reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a
- reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e
- getLocAnn :: Located a -> SrcSpanAnnA
- getLocA :: GenLocated (SrcSpanAnn' a) e -> SrcSpan
- noLocA :: a -> LocatedAn an a
- noAnnSrcSpan :: SrcSpan -> SrcAnn ann
- noSrcSpanA :: SrcAnn ann
- noAnn :: EpAnn a
- addAnns :: EpAnn [AddEpAnn] -> [AddEpAnn] -> EpAnnComments -> EpAnn [AddEpAnn]
- addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA
- widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan
- widenAnchor :: Anchor -> [AddEpAnn] -> Anchor
- widenAnchorR :: Anchor -> RealSrcSpan -> Anchor
- widenLocatedAn :: SrcSpanAnn' an -> [AddEpAnn] -> SrcSpanAnn' an
- epAnnAnnsL :: EpAnn a -> [a]
- epAnnAnns :: EpAnn [AddEpAnn] -> [AddEpAnn]
- annParen2AddEpAnn :: EpAnn AnnParen -> [AddEpAnn]
- epAnnComments :: EpAnn an -> EpAnnComments
- sortLocatedA :: [GenLocated (SrcSpanAnn' a) e] -> [GenLocated (SrcSpanAnn' a) e]
- mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b
- combineLocsA :: Semigroup a => GenLocated (SrcAnn a) e1 -> GenLocated (SrcAnn a) e2 -> SrcAnn a
- combineSrcSpansA :: Semigroup a => SrcAnn a -> SrcAnn a -> SrcAnn a
- addCLocA :: GenLocated (SrcSpanAnn' a) e1 -> GenLocated SrcSpan e2 -> e3 -> GenLocated (SrcAnn ann) e3
- addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> e3 -> GenLocated (SrcAnn ann) e3
- getFollowingComments :: EpAnnComments -> [LEpaComment]
- setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- noComments :: EpAnnCO
- placeholderRealSpan :: RealSrcSpan
- comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO
- addCommentsToSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann
- setCommentsSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann
- addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a
- setCommentsEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a
- transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann
- removeCommentsA :: SrcAnn ann -> SrcAnn ann
- pprIfPs :: forall (p :: Pass). IsPass p => (p ~ 'Parsed => SDoc) -> SDoc
- pprIfRn :: forall (p :: Pass). IsPass p => (p ~ 'Renamed => SDoc) -> SDoc
- pprIfTc :: forall (p :: Pass). IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc
- noHsTok :: forall (tok :: Symbol). GenLocated TokenLocation (HsToken tok)
- noHsUniTok :: forall (tok :: Symbol) (utok :: Symbol). GenLocated TokenLocation (HsUniToken tok utok)
- hsDocIds :: WithHsDocIdentifiers a GhcRn -> NameSet
- pprWithDoc :: LHsDoc name -> SDoc -> SDoc
- pprMaybeWithDoc :: Maybe (LHsDoc name) -> SDoc -> SDoc
- pprHsDocDebug :: Outputable (IdP name) => HsDoc name -> SDoc
- emptyDocs :: Docs
- importDeclQualifiedStyle :: Maybe EpaLocation -> Maybe EpaLocation -> (Maybe EpaLocation, ImportDeclQualifiedStyle)
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- simpleImportDecl :: ModuleName -> ImportDecl GhcPs
- ieName :: forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p)
- ieNames :: forall (p :: Pass). IE (GhcPass p) -> [IdP (GhcPass p)]
- ieWrappedLName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- ieWrappedName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
- lieWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> IdP (GhcPass p)
- ieLWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- replaceWrappedName :: IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn
- replaceLWrappedName :: LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
- negateOverLitVal :: OverLitVal -> OverLitVal
- hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr () pass]
- hsPatSigType :: HsPatSigType pass -> LHsType pass
- mapHsOuterImplicit :: (XHsOuterImplicit pass -> XHsOuterImplicit pass) -> HsOuterTyVarBndrs flag pass -> HsOuterTyVarBndrs flag pass
- hsIPNameFS :: HsIPName -> FastString
- isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool
- hsMult :: HsScaled pass a -> HsArrow pass
- hsScaledThing :: HsScaled pass a -> a
- noTypeArgs :: [Void]
- hsConPatArgs :: UnXRec p => HsConPatDetails p -> [LPat p]
- hsRecFields :: UnXRec p => HsRecFields p arg -> [XCFieldOcc p]
- hsRecFieldsArgs :: UnXRec p => HsRecFields p arg -> [arg]
- hsRecFieldSel :: UnXRec p => HsRecField p arg -> XCFieldOcc p
- pprLPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> SDoc
- isFixityLSig :: UnXRec p => LSig p -> Bool
- isTypeLSig :: UnXRec p => LSig p -> Bool
- isSpecLSig :: UnXRec p => LSig p -> Bool
- isSpecInstLSig :: UnXRec p => LSig p -> Bool
- isPragLSig :: UnXRec p => LSig p -> Bool
- isInlineLSig :: UnXRec p => LSig p -> Bool
- isMinimalLSig :: UnXRec p => LSig p -> Bool
- isSCCFunSig :: UnXRec p => LSig p -> Bool
- isCompleteMatchSig :: UnXRec p => LSig p -> Bool
- hsGroupInstDecls :: HsGroup id -> [LInstDecl id]
- isDataDecl :: TyClDecl pass -> Bool
- isSynDecl :: TyClDecl pass -> Bool
- isClassDecl :: TyClDecl pass -> Bool
- isFamilyDecl :: TyClDecl pass -> Bool
- isTypeFamilyDecl :: TyClDecl pass -> Bool
- isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool
- isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool
- isDataFamilyDecl :: TyClDecl pass -> Bool
- tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass
- tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass]
- tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass]
- tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass]
- tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass]
- dataDefnConsNewOrData :: DataDefnCons a -> NewOrData
- isTypeDataDefnCons :: DataDefnCons a -> Bool
- collectRuleBndrSigTys :: [RuleBndr pass] -> [HsPatSigType pass]
- docDeclDoc :: DocDecl pass -> LHsDoc pass
- annProvenanceName_maybe :: UnXRec p => AnnProvenance p -> Maybe (IdP p)
- isInfixMatch :: Match id body -> Bool
- isPatSynCtxt :: HsMatchContext p -> Bool
- qualifiedDoModuleName_maybe :: HsStmtContext p -> Maybe ModuleName
- isComprehensionContext :: HsStmtContext id -> Bool
- isDoComprehensionContext :: HsDoFlavour -> Bool
- isMonadStmtContext :: HsStmtContext id -> Bool
- isMonadDoStmtContext :: HsDoFlavour -> Bool
- isMonadCompContext :: HsStmtContext id -> Bool
- isMonadDoCompContext :: HsDoFlavour -> Bool
- pprFunBind :: forall (idR :: Pass). OutputableBndrId idR => MatchGroup (GhcPass idR) (LHsExpr (GhcPass idR)) -> SDoc
- pprPatBind :: forall (bndr :: Pass) (p :: Pass). (OutputableBndrId bndr, OutputableBndrId p) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) (LHsExpr (GhcPass p)) -> SDoc
- pprUntypedSplice :: forall (p :: Pass). OutputableBndrId p => Bool -> Maybe SplicePointName -> HsUntypedSplice (GhcPass p) -> SDoc
- pprTypedSplice :: forall (p :: Pass). OutputableBndrId p => Maybe SplicePointName -> LHsExpr (GhcPass p) -> SDoc
- pprExpr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- pprLExpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc
- getBangType :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
- getBangStrictness :: forall (p :: Pass). LHsType (GhcPass p) -> HsSrcBang
- fromMaybeContext :: forall (p :: Pass). Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
- mkHsForAllVisTele :: forall (p :: Pass). EpAnnForallTy -> [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p)
- mkHsForAllInvisTele :: forall (p :: Pass). EpAnnForallTy -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p)
- mkHsQTvs :: [LHsTyVarBndr () GhcPs] -> LHsQTyVars GhcPs
- emptyLHsQTvs :: LHsQTyVars GhcRn
- hsSigWcType :: UnXRec p => LHsSigWcType p -> LHsType p
- dropWildCards :: LHsSigWcType pass -> LHsSigType pass
- hsOuterTyVarNames :: HsOuterTyVarBndrs flag GhcRn -> [Name]
- hsOuterExplicitBndrs :: forall flag (p :: Pass). HsOuterTyVarBndrs flag (GhcPass p) -> [LHsTyVarBndr flag (NoGhcTc (GhcPass p))]
- mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs
- mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs] -> HsOuterTyVarBndrs flag GhcPs
- mkHsImplicitSigType :: LHsType GhcPs -> HsSigType GhcPs
- mkHsExplicitSigType :: EpAnnForallTy -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs -> HsSigType GhcPs
- mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing
- mkHsPatSigType :: EpAnnCO -> LHsType GhcPs -> HsPatSigType GhcPs
- mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing
- hsTyVarBndrFlag :: forall flag (pass :: Pass). HsTyVarBndr flag (GhcPass pass) -> flag
- setHsTyVarBndrFlag :: forall flag flag' (pass :: Pass). flag -> HsTyVarBndr flag' (GhcPass pass) -> HsTyVarBndr flag (GhcPass pass)
- hsTvbAllKinded :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> Bool
- hsLinear :: forall a (p :: Pass). a -> HsScaled (GhcPass p) a
- hsUnrestricted :: forall a (p :: Pass). a -> HsScaled (GhcPass p) a
- isUnrestricted :: HsArrow GhcRn -> Bool
- arrowToHsType :: HsArrow GhcRn -> LHsType GhcRn
- pprHsArrow :: forall (pass :: Pass). OutputableBndrId pass => HsArrow (GhcPass pass) -> SDoc
- hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name]
- hsScopedTvs :: LHsSigType GhcRn -> [Name]
- hsTyVarName :: forall flag (p :: Pass). HsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p)
- hsLTyVarName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p)
- hsLTyVarNames :: forall flag (p :: Pass). [LHsTyVarBndr flag (GhcPass p)] -> [IdP (GhcPass p)]
- hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)]
- hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name]
- hsLTyVarLocName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> LocatedN (IdP (GhcPass p))
- hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LocatedN (IdP (GhcPass p))]
- hsTyKindSig :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (LHsKind (GhcPass p))
- ignoreParens :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkAnonWildCardTy :: HsType GhcPs
- mkHsOpTy :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => PromotionFlag -> LHsType (GhcPass p) -> LocatedN (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p)
- mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkHsAppTys :: 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)
- splitHsFunType :: forall (p :: Pass). LHsType (GhcPass p) -> ([AddEpAnn], EpAnnComments, [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p))
- hsTyGetAppHead_maybe :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => LHsType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p)))
- lhsTypeArgSrcSpan :: forall (pass :: Pass). LHsTypeArg (GhcPass pass) -> SrcSpan
- numVisibleArgs :: [HsArg tm ty] -> Arity
- pprHsArgsApp :: (OutputableBndr id, Outputable tm, Outputable ty) => id -> LexicalFixity -> [HsArg tm ty] -> SDoc
- 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))
- splitLHsSigmaTyInvis :: forall (p :: Pass). LHsType (GhcPass p) -> ([LHsTyVarBndr Specificity (GhcPass p)], Maybe (LHsContext (GhcPass p)), LHsType (GhcPass p))
- splitLHsGadtTy :: LHsSigType GhcPs -> (HsOuterSigTyVarBndrs GhcPs, Maybe (LHsContext GhcPs), LHsType GhcPs)
- splitLHsForAllTyInvis :: forall (pass :: Pass). LHsType (GhcPass pass) -> ((EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass))
- splitLHsForAllTyInvis_KP :: forall (pass :: Pass). LHsType (GhcPass pass) -> (Maybe (EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass))
- splitLHsQualTy :: forall (pass :: Pass). LHsType (GhcPass pass) -> (Maybe (LHsContext (GhcPass pass)), LHsType (GhcPass pass))
- splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], Maybe (LHsContext GhcRn), LHsType GhcRn)
- getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
- getLHsInstDeclClass_maybe :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => LHsSigType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p)))
- mkFieldOcc :: LocatedN RdrName -> FieldOcc GhcPs
- mkAmbiguousFieldOcc :: LocatedN RdrName -> AmbiguousFieldOcc GhcPs
- rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName
- selectorAmbiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> Id
- unambiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> FieldOcc GhcTc
- ambiguousFieldOcc :: FieldOcc GhcTc -> AmbiguousFieldOcc GhcTc
- pprAnonWildCard :: SDoc
- pprHsOuterFamEqnTyVarBndrs :: forall (p :: Pass). OutputableBndrId p => HsOuterFamEqnTyVarBndrs (GhcPass p) -> SDoc
- pprHsOuterSigTyVarBndrs :: forall (p :: Pass). OutputableBndrId p => HsOuterSigTyVarBndrs (GhcPass p) -> SDoc
- pprHsForAll :: forall (p :: Pass). OutputableBndrId p => HsForAllTelescope (GhcPass p) -> Maybe (LHsContext (GhcPass p)) -> SDoc
- pprLHsContext :: forall (p :: Pass). OutputableBndrId p => Maybe (LHsContext (GhcPass p)) -> SDoc
- pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc
- pprHsType :: forall (p :: Pass). OutputableBndrId p => HsType (GhcPass p) -> SDoc
- hsTypeNeedsParens :: forall (p :: Pass). PprPrec -> HsType (GhcPass p) -> Bool
- parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p)
- pprXOverLit :: forall (p :: Pass). GhcPass p -> XOverLit (GhcPass p) -> SDoc
- overLitType :: HsOverLit GhcTc -> Type
- hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool
- hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
- convertLit :: forall (p1 :: Pass) (p2 :: Pass). HsLit (GhcPass p1) -> HsLit (GhcPass p2)
- pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc
- pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc]
- pprDeclList :: [SDoc] -> SDoc
- emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b)
- eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
- isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool
- emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- emptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR
- isEmptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR -> Bool
- plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a)
- ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc
- pprTicks :: SDoc -> SDoc -> SDoc
- isEmptyIPBindsPR :: forall (p :: Pass). HsIPBinds (GhcPass p) -> Bool
- isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool
- noSpecPrags :: TcSpecPrags
- hasSpecPrags :: TcSpecPrags -> Bool
- isDefaultMethod :: TcSpecPrags -> Bool
- ppr_sig :: forall (p :: Pass). OutputableBndrId p => Sig (GhcPass p) -> SDoc
- hsSigDoc :: forall (p :: Pass). IsPass p => Sig (GhcPass p) -> SDoc
- extractSpecPragName :: SourceText -> String
- pragBrackets :: SDoc -> SDoc
- pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc
- pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc
- pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc
- pprTcSpecPrags :: TcSpecPrags -> SDoc
- pprMinimalSig :: OutputableBndr name => LBooleanFormula (GenLocated l name) -> SDoc
- hsRecFieldId :: HsRecField GhcTc arg -> Id
- hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName
- hsRecUpdFieldId :: HsFieldBind (LAmbiguousFieldOcc GhcTc) arg -> Located Id
- hsRecUpdFieldOcc :: HsFieldBind (LAmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc
- pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc
- pprConArgs :: forall (p :: Pass). (OutputableBndrId p, Outputable (Anno (IdGhcP p))) => HsConPatDetails (GhcPass p) -> SDoc
- mkPrefixConPat :: DataCon -> [LPat GhcTc] -> [Type] -> LPat GhcTc
- mkNilPat :: Type -> LPat GhcTc
- mkCharLitPat :: SourceText -> Char -> LPat GhcTc
- isBangedLPat :: forall (p :: Pass). LPat (GhcPass p) -> Bool
- looksLazyPatBind :: HsBind GhcTc -> Bool
- isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => DynFlags -> LPat (GhcPass p) -> Bool
- isSimplePat :: forall (x :: Pass). LPat (GhcPass x) -> Maybe (IdP (GhcPass x))
- patNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> Pat (GhcPass p) -> Bool
- gParPat :: forall (pass :: Pass). LPat (GhcPass pass) -> Pat (GhcPass pass)
- parenthesizePat :: forall (p :: Pass). IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p)
- collectEvVarsPats :: [Pat GhcTc] -> Bag EvVar
- collectEvVarsPat :: Pat GhcTc -> Bag EvVar
- partitionBindsAndSigs :: [LHsDecl GhcPs] -> (LHsBinds GhcPs, [LSig GhcPs], [LFamilyDecl GhcPs], [LTyFamInstDecl GhcPs], [LDataFamInstDecl GhcPs], [LDocDecl GhcPs])
- emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- hsGroupTopLevelFixitySigs :: forall (p :: Pass). HsGroup (GhcPass p) -> [LFixitySig (GhcPass p)]
- appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p)
- tyFamInstDeclName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyFamInstDecl (GhcPass p) -> IdP (GhcPass p)
- tyFamInstDeclLName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyFamInstDecl (GhcPass p) -> LocatedN (IdP (GhcPass p))
- tyClDeclLName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyClDecl (GhcPass p) -> LocatedN (IdP (GhcPass p))
- countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int)
- tcdName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyClDecl (GhcPass p) -> IdP (GhcPass p)
- hsDeclHasCusk :: TyClDecl GhcRn -> Bool
- pp_vanilla_decl_head :: forall (p :: Pass). OutputableBndrId p => XRec (GhcPass p) (IdP (GhcPass p)) -> LHsQTyVars (GhcPass p) -> LexicalFixity -> Maybe (LHsContext (GhcPass p)) -> SDoc
- pprTyClDeclFlavour :: forall (p :: Pass). TyClDecl (GhcPass p) -> SDoc
- familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> XRec (GhcPass p) (IdP (GhcPass p))
- familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p)
- famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p))
- resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a))
- derivStrategyName :: DerivStrategy a -> SDoc
- standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
- getConNames :: ConDecl GhcRn -> [LocatedN Name]
- getRecConArgs_maybe :: ConDecl GhcRn -> Maybe (LocatedL [LConDeclField GhcRn])
- hsConDeclTheta :: forall (p :: Pass). Maybe (LHsContext (GhcPass p)) -> [LHsType (GhcPass p)]
- ppDataDefnHeader :: forall (p :: Pass). OutputableBndrId p => (Maybe (LHsContext (GhcPass p)) -> SDoc) -> HsDataDefn (GhcPass p) -> SDoc
- pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc
- pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc
- pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> HsOuterFamEqnTyVarBndrs (GhcPass p) -> HsTyPats (GhcPass p) -> LexicalFixity -> Maybe (LHsContext (GhcPass p)) -> SDoc
- instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)]
- newOrDataToFlavour :: NewOrData -> TyConFlavour
- anyLConIsGadt :: Foldable f => f (GenLocated l (ConDecl pass)) -> Bool
- foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r
- mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p
- flattenRuleDecls :: forall (p :: Pass). [LRuleDecls (GhcPass p)] -> [LRuleDecl (GhcPass p)]
- pprFullRuleName :: SourceText -> GenLocated a RuleName -> SDoc
- roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p)
- noExpr :: forall (p :: Pass). HsExpr (GhcPass p)
- noSyntaxExpr :: forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p)
- mkSyntaxExpr :: HsExpr GhcRn -> SyntaxExprRn
- mkRnSyntaxExpr :: Name -> SyntaxExprRn
- tupArgPresent :: forall (p :: Pass). HsTupArg (GhcPass p) -> Bool
- isQuietHsExpr :: HsExpr id -> Bool
- pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- ppr_lexpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- ppr_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc
- ppr_infix_expr_rn :: HsExpansion (HsExpr GhcRn) (HsExpr GhcRn) -> Maybe SDoc
- ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc
- ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc
- pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- hsExprNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> HsExpr (GhcPass p) -> Bool
- gHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> HsExpr (GhcPass id)
- parenthesizeHsExpr :: forall (p :: Pass). IsPass p => PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- stripParensLHsExpr :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- stripParensHsExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> HsExpr (GhcPass p)
- isAtomicHsExpr :: forall (p :: Pass). IsPass p => HsExpr (GhcPass p) -> Bool
- pprLCmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- pprCmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- isQuietHsCmd :: HsCmd id -> Bool
- ppr_lcmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- ppr_cmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- pprCmdArg :: forall (p :: Pass). OutputableBndrId p => HsCmdTop (GhcPass p) -> SDoc
- isEmptyMatchGroup :: forall (p :: Pass) body. MatchGroup (GhcPass p) body -> Bool
- isSingletonMatchGroup :: forall (p :: Pass) body. [LMatch (GhcPass p) body] -> Bool
- matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity
- hsLMatchPats :: forall (id :: Pass) body. LMatch (GhcPass id) body -> [LPat (GhcPass id)]
- pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc
- pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> 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
- pp_rhs :: Outputable body => HsMatchContext passL -> 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
- pprBindStmt :: (Outputable pat, Outputable expr) => pat -> expr -> SDoc
- pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> 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
- pprBy :: Outputable body => Maybe body -> SDoc
- pprDo :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => HsDoFlavour -> [LStmt (GhcPass p) body] -> SDoc
- pprArrowExpr :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc
- ppr_module_name_prefix :: Maybe ModuleName -> 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
- pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc
- pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc
- pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc
- ppr_quasi :: OutputableBndr p => p -> FastString -> SDoc
- ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> Maybe SplicePointName -> LHsExpr (GhcPass p) -> SDoc
- thBrackets :: SDoc -> SDoc -> SDoc
- thTyBrackets :: SDoc -> SDoc
- ppr_with_pending_tc_splices :: SDoc -> [PendingTcSplice] -> SDoc
- pp_dotdot :: SDoc
- lamCaseKeyword :: LamCaseVariant -> SDoc
- pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc
- pprHsArrType :: HsArrAppType -> SDoc
- matchContextErrString :: forall (p :: Pass). OutputableBndrId p => HsMatchContext (GhcPass p) -> SDoc
- matchArrowContextErrString :: HsArrowMatchContext -> SDoc
- matchDoContextErrString :: HsDoFlavour -> SDoc
- pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc
- pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) (ctx :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId ctx, Outputable body, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA) => HsStmtContext (GhcPass ctx) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc
- matchSeparator :: HsMatchContext p -> SDoc
- pprMatchContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc
- pprMatchContextNoun :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc
- pprMatchContextNouns :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc
- pprArrowMatchContextNoun :: HsArrowMatchContext -> SDoc
- pprArrowMatchContextNouns :: HsArrowMatchContext -> SDoc
- pprAStmtContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsStmtContext p -> SDoc
- pprStmtContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsStmtContext p -> SDoc
- pprStmtCat :: forall (p :: Pass) body. Stmt (GhcPass p) body -> SDoc
- pprAHsDoFlavour :: HsDoFlavour -> SDoc
- pprHsDoFlavour :: HsDoFlavour -> SDoc
- prependQualified :: Maybe ModuleName -> SDoc -> SDoc
- pprFieldLabelStrings :: (UnXRec p, Outputable (XRec p FieldLabelString)) => FieldLabelStrings p -> SDoc
- pprPrefixFastString :: FastString -> SDoc
- mkHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns) => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p)))
- unguardedGRHSs :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => SrcSpan -> LocatedA (body (GhcPass p)) -> EpAnn GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p)))
- unguardedRHS :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => EpAnn GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) -> [LGRHS (GhcPass p) (LocatedA (body (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)))
- mkLamCaseMatchGroup :: forall (p :: Pass) body. AnnoBody p body => Origin -> LamCaseVariant -> LocatedL [LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))] -> MatchGroup (GhcPass p) (LocatedA (body (GhcPass p)))
- mkLocatedList :: Semigroup a => [GenLocated (SrcAnn a) e2] -> LocatedAn an [GenLocated (SrcAnn a) e2]
- mkHsApp :: 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)
- mkHsApps :: forall (id :: Pass). LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- 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)
- mkHsAppType :: LHsExpr GhcRn -> LHsWcType GhcRn -> LHsExpr GhcRn
- mkHsAppTypes :: LHsExpr GhcRn -> [LHsWcType GhcRn] -> LHsExpr GhcRn
- mkHsLam :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsCaseAlt :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns, Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA) => LPat (GhcPass p) -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p)))
- nlHsTyApp :: Id -> [Type] -> LHsExpr GhcTc
- nlHsTyApps :: Id -> [Type] -> [LHsExpr GhcTc] -> LHsExpr GhcTc
- mkLHsPar :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkParPat :: forall (p :: Pass). IsPass p => LPat (GhcPass p) -> LPat (GhcPass p)
- nlParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name)
- 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
- mkHsIntegral :: IntegralLit -> HsOverLit GhcPs
- mkHsFractional :: FractionalLit -> HsOverLit GhcPs
- mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs
- mkHsDo :: HsDoFlavour -> LocatedL [ExprLStmt GhcPs] -> HsExpr GhcPs
- mkHsDoAnns :: HsDoFlavour -> LocatedL [ExprLStmt GhcPs] -> EpAnn AnnList -> HsExpr GhcPs
- mkHsComp :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsCompAnns :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> EpAnn AnnList -> HsExpr GhcPs
- mkHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> EpAnn AnnsIf -> HsExpr GhcPs
- mkHsCmdIf :: LHsExpr GhcPs -> LHsCmd GhcPs -> LHsCmd GhcPs -> EpAnn AnnsIf -> HsCmd GhcPs
- mkNPat :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpAnn [AddEpAnn] -> Pat GhcPs
- mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpAnn EpaLocation -> Pat GhcPs
- emptyTransStmt :: EpAnn [AddEpAnn] -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformByStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkGroupUsingStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkGroupByUsingStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkLastStmt :: forall (idR :: Pass) bodyR (idL :: Pass). IsPass idR => LocatedA (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (LocatedA (bodyR (GhcPass idR)))
- mkBodyStmt :: forall bodyR (idL :: Pass). LocatedA (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (LocatedA (bodyR GhcPs))
- mkPsBindStmt :: EpAnn [AddEpAnn] -> LPat GhcPs -> LocatedA (bodyR GhcPs) -> StmtLR GhcPs GhcPs (LocatedA (bodyR GhcPs))
- mkRnBindStmt :: LPat GhcRn -> LocatedA (bodyR GhcRn) -> StmtLR GhcRn GhcRn (LocatedA (bodyR GhcRn))
- mkTcBindStmt :: LPat GhcTc -> LocatedA (bodyR GhcTc) -> StmtLR GhcTc GhcTc (LocatedA (bodyR GhcTc))
- unitRecStmtTc :: RecStmtTc
- emptyRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => StmtLR (GhcPass idL) GhcPs bodyR
- emptyRecStmtName :: Anno [GenLocated (Anno (StmtLR GhcRn GhcRn bodyR)) (StmtLR GhcRn GhcRn bodyR)] ~ SrcSpanAnnL => StmtLR GhcRn GhcRn bodyR
- emptyRecStmtId :: Stmt GhcTc (LocatedA (HsCmd GhcTc))
- mkLetStmt :: EpAnn [AddEpAnn] -> HsLocalBinds GhcPs -> StmtLR GhcPs GhcPs (LocatedA b)
- mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsString :: forall (p :: Pass). String -> HsLit (GhcPass p)
- mkHsStringFS :: forall (p :: Pass). FastString -> HsLit (GhcPass p)
- mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p)
- mkHsCharPrimLit :: forall (p :: Pass). Char -> HsLit (GhcPass p)
- mkConLikeTc :: ConLike -> HsExpr GhcTc
- nlHsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LHsExpr (GhcPass p)
- nl_HsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> HsExpr (GhcPass p)
- nlHsDataCon :: DataCon -> LHsExpr GhcTc
- nlHsLit :: forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p)
- nlHsIntLit :: forall (p :: Pass). Integer -> LHsExpr (GhcPass p)
- nlVarPat :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LPat (GhcPass p)
- nlLitPat :: HsLit GhcPs -> LPat GhcPs
- nlHsApp :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsSyntaxApps :: SyntaxExprTc -> [LHsExpr GhcTc] -> LHsExpr GhcTc
- nlHsApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [LHsExpr (GhcPass p)] -> LHsExpr (GhcPass p)
- nlHsVarApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [IdP (GhcPass p)] -> LHsExpr (GhcPass p)
- nlConVarPat :: RdrName -> [RdrName] -> LPat GhcPs
- nlConVarPatName :: Name -> [Name] -> LPat GhcRn
- nlInfixConPat :: RdrName -> LPat GhcPs -> LPat GhcPs -> LPat GhcPs
- nlConPat :: RdrName -> [LPat GhcPs] -> LPat GhcPs
- nlConPatName :: Name -> [LPat GhcRn] -> LPat GhcRn
- nlNullaryConPat :: RdrName -> LPat GhcPs
- nlWildConPat :: DataCon -> LPat GhcPs
- nlWildPat :: LPat GhcPs
- nlWildPatName :: LPat GhcRn
- nlHsDo :: HsDoFlavour -> [LStmt GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
- nlHsLam :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
- nlHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
- nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlList :: [LHsExpr GhcPs] -> LHsExpr GhcPs
- nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> IdP (GhcPass p) -> LHsType (GhcPass p)
- nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsParTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyConApp :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> LexicalFixity -> IdP (GhcPass p) -> [LHsTypeArg (GhcPass p)] -> LHsType (GhcPass p)
- nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p)
- mkLHsTupleExpr :: forall (p :: Pass). [LHsExpr (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p)
- mkLHsVarTuple :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p)
- nlTuplePat :: [LPat GhcPs] -> Boxity -> LPat GhcPs
- missingTupArg :: EpAnn EpaLocation -> HsTupArg GhcPs
- mkBigLHsVarTup :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p)
- mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> XExplicitTuple (GhcPass id) -> LHsExpr (GhcPass id)
- mkBigLHsVarPatTup :: [IdP GhcRn] -> LPat GhcRn
- mkBigLHsPatTup :: [LPat GhcRn] -> LPat GhcRn
- hsTypeToHsSigType :: LHsType GhcPs -> LHsSigType GhcPs
- hsTypeToHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs
- mkHsSigEnv :: (LSig GhcRn -> Maybe ([LocatedN Name], a)) -> [LSig GhcRn] -> NameEnv a
- mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs]
- mkLHsWrap :: HsWrapper -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsWrap :: HsWrapper -> HsExpr GhcTc -> HsExpr GhcTc
- mkHsWrapCo :: TcCoercionN -> HsExpr GhcTc -> HsExpr GhcTc
- mkHsWrapCoR :: TcCoercionR -> HsExpr GhcTc -> HsExpr GhcTc
- mkLHsWrapCo :: TcCoercionN -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsCmdWrap :: HsWrapper -> HsCmd GhcTc -> HsCmd GhcTc
- mkLHsCmdWrap :: HsWrapper -> LHsCmd GhcTc -> LHsCmd GhcTc
- mkHsWrapPat :: HsWrapper -> Pat GhcTc -> Type -> Pat GhcTc
- mkHsWrapPatCo :: TcCoercionN -> Pat GhcTc -> Type -> Pat GhcTc
- mkHsDictLet :: TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkFunBind :: Origin -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs
- mkTopFunBind :: Origin -> LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn
- mkHsVarBind :: SrcSpan -> RdrName -> LHsExpr GhcPs -> LHsBind GhcPs
- mkVarBind :: forall (p :: Pass). IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p)
- mkPatSynBind :: LocatedN RdrName -> HsPatSynDetails GhcPs -> LPat GhcPs -> HsPatSynDir GhcPs -> EpAnn [AddEpAnn] -> HsBind GhcPs
- isInfixFunBind :: forall id1 id2. UnXRec id2 => HsBindLR id1 id2 -> Bool
- spanHsLocaLBinds :: forall (p :: Pass). HsLocalBinds (GhcPass p) -> SrcSpan
- mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs
- mkPrefixFunRhs :: LIdP (NoGhcTc p) -> HsMatchContext p
- mkMatch :: forall (p :: Pass). IsPass p => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> HsLocalBinds (GhcPass p) -> LMatch (GhcPass p) (LHsExpr (GhcPass p))
- isUnliftedHsBind :: HsBind GhcTc -> Bool
- isBangedHsBind :: HsBind GhcTc -> Bool
- collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsLocalBindsLR (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)]
- collectHsValBinders :: forall (idL :: Pass) idR. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) idR -> [IdP (GhcPass idL)]
- collectHsBindBinders :: CollectPass p => CollectFlag p -> HsBindLR p idR -> [IdP p]
- collectHsBindsBinders :: CollectPass p => CollectFlag p -> LHsBindsLR p idR -> [IdP p]
- collectHsBindListBinders :: CollectPass p => CollectFlag p -> [LHsBindLR p idR] -> [IdP p]
- collectMethodBinders :: UnXRec idL => LHsBindsLR idL idR -> [LIdP idL]
- collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)]
- collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [StmtLR (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)]
- collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)]
- collectPatBinders :: CollectPass p => CollectFlag p -> LPat p -> [IdP p]
- collectPatsBinders :: CollectPass p => CollectFlag p -> [LPat p] -> [IdP p]
- hsGroupBinders :: HsGroup GhcRn -> [Name]
- hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name]
- hsLTyClDeclBinders :: forall (p :: Pass). IsPass p => LocatedA (TyClDecl (GhcPass p)) -> ([LocatedA (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- hsForeignDeclsBinders :: forall (p :: Pass) a. (UnXRec (GhcPass p), IsSrcSpanAnn p a) => [LForeignDecl (GhcPass p)] -> [LIdP (GhcPass p)]
- hsPatSynSelectors :: forall (p :: Pass). IsPass p => HsValBinds (GhcPass p) -> [FieldOcc (GhcPass p)]
- getPatSynBinds :: UnXRec id => [(RecFlag, LHsBinds id)] -> [PatSynBind id id]
- hsDataFamInstBinders :: forall (p :: Pass). IsPass p => DataFamInstDecl (GhcPass p) -> ([LocatedA (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- lStmtsImplicits :: forall (idR :: Pass) (body :: Type -> Type). [LStmtLR GhcRn (GhcPass idR) (LocatedA (body (GhcPass idR)))] -> [(SrcSpan, [Name])]
- hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])]
- lPatImplicits :: LPat GhcRn -> [(SrcSpan, [Name])]
- nameOccName :: Name -> OccName
- occName :: HasOccName name => name -> OccName
- occNameString :: OccName -> String
- ppr :: Outputable a => a -> SDoc
- showSDocUnsafe :: SDoc -> String
- handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a
- data RdrName
- rdrNameOcc :: RdrName -> OccName
- data GenLocated l e = L l e
- pattern RealSrcLoc' :: RealSrcLoc -> SrcLoc
- pattern RealSrcSpan' :: RealSrcSpan -> SrcSpan
- data RealSrcSpan
- type SrcSpanLess a = a
- combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
- composeSrcSpan :: a -> a
- decomposeSrcSpan :: a -> a
- stringToStringBuffer :: String -> StringBuffer
- impliedXFlags :: [(Extension, TurnOnFlag, Extension)]
- type FunBind = HsMatchContext GhcPs
- 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)
- type Module = Located (HsModule GhcPs)
- type MonadFail' = MonadFail
- type ReplaceWorker a mod = (Data a, Data mod) => mod -> Parser (LocatedA a) -> Int -> Refactoring SrcSpan -> IO mod
- annSpanToSrcSpan :: AnnSpan -> SrcSpan
- badAnnSpan :: AnnSpan
- mkErr :: DynFlags -> SrcSpan -> String -> Errors
- parseModuleName :: SrcSpan -> Parser (LocatedA ModuleName)
- setAnnSpanFile :: FastString -> AnnSpan -> AnnSpan
- setRealSrcSpanFile :: FastString -> RealSrcSpan -> RealSrcSpan
- setSrcSpanFile :: FastString -> SrcSpan -> SrcSpan
- srcSpanToAnnSpan :: SrcSpan -> AnnSpan
- type AnnSpan = RealSrcSpan
- commentSrcSpan :: LEpaComment -> SrcSpan
- ann :: SrcSpanAnn' a -> a
- transferEntryDP :: forall (m :: Type -> Type) t2 t1 a b. (Monad m, Monoid t2, Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> TransformT m (LocatedAn t2 b)
- transferEntryDP' :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs)
- type AnnConstraint an = Monoid an
- showAst :: Data a => a -> String
- initParserOpts :: DynFlags -> ParserOpts
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 | |
AnnBang |
|
AnnBackquote | '`' |
AnnBy | |
AnnCase | case or lambda case |
AnnCases | lambda cases |
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 |
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
|
AnnOpenB | '(|' |
AnnOpenBU | '(|', unicode variant |
AnnOpenC | '{' |
AnnOpenE | '[e|' or '[e||' |
AnnOpenEQ | '[|' |
AnnOpenEQU | '[|', unicode variant |
AnnOpenP | '(' |
AnnOpenS | '[' |
AnnOpenPH | '(#' |
AnnDollar | prefix |
AnnDollarDollar | prefix |
AnnPackageName | |
AnnPattern | |
AnnPercent |
|
AnnPercentOne | '%1' -- for HsLinearArrow |
AnnProc | |
AnnQualified | |
AnnRarrow |
|
AnnRarrowU |
|
AnnRec | |
AnnRole | |
AnnSafe | |
AnnSemi | ';' |
AnnSimpleQuote | ''' |
AnnSignature | |
AnnStatic |
|
AnnStock | |
AnnThen | |
AnnThTyQuote | double ''' |
AnnTilde | |
AnnType | |
AnnUnit |
|
AnnUsing | |
AnnVal | e.g. INTEGER |
AnnValStr | String value, will need quotes when output |
AnnVbar | '|' |
AnnVia |
|
AnnWhere | |
Annlarrowtail |
|
AnnlarrowtailU |
|
Annrarrowtail |
|
AnnrarrowtailU |
|
AnnLarrowtail |
|
AnnLarrowtailU |
|
AnnRarrowtail |
|
AnnRarrowtailU |
|
Instances
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
Data DeltaPos | |
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 | |
Outputable DeltaPos | |
Defined in GHC.Parser.Annotation | |
Eq DeltaPos | |
Ord DeltaPos | |
Defined in GHC.Parser.Annotation |
BasicTypes / GHC.Types.Basic
Constructors
Fixity SourceText Int FixityDirection |
Instances
Data Fixity | |
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 | |
Outputable Fixity | |
Defined in GHC.Types.Fixity | |
Eq Fixity | |
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
DynFlags / GHC.Driver.Session
Constructors
FlagSpec | |
Fields
|
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
Enum GeneralFlag | |
Defined in GHC.Driver.Flags Methods succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
Show GeneralFlag | |
Defined in GHC.Driver.Flags Methods showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # | |
Eq GeneralFlag | |
Defined in GHC.Driver.Flags |
gopt_set :: DynFlags -> GeneralFlag -> DynFlags #
Set a GeneralFlag
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags #
Unset a GeneralFlag
Arguments
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Warn]) | Updated |
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.
ErrUtils
type Errors = ErrorMessages Source #
type ErrorMessages = Messages GhcMessage #
A collection of error messages.
INVARIANT: Each GhcMessage
in the collection should have SevError
severity.
FastString / GHC.Data.FastString
data FastString #
A FastString
is a UTF-8 encoded string together with a unique ID. All
FastString
s 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
mkFastString :: String -> FastString #
Creates a UTF-8 encoded FastString
from a String
HeaderInfo / GHC.Parser.Header
Arguments
:: ParserOpts | |
-> StringBuffer | Input Buffer |
-> FilePath | Source filename. Used for location info. |
-> (Messages PsMessage, [Located String]) | warnings and 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
Guarded Right Hand Side.
Constructors
GRHS (XCGRHS p body) [GuardLStmt p] body | |
XGRHS !(XXGRHS p body) |
Instances
A Haskell expression.
Constructors
HsVar (XVar p) (LIdP p) | Variable See Note [Located RdrNames] |
HsUnboundVar (XUnboundVar p) RdrName | 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. |
HsRecSel (XRecSel p) (FieldOcc p) | Variable pointing to record selector See Note [Non-overloaded record field selectors] and Note [Record selectors in the AST] |
HsOverLabel (XOverLabel p) SourceText FastString | Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels) Note [Pragma source text] in GHC.Types.SourceText |
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) LamCaseVariant (MatchGroup p (LHsExpr p)) | Lambda-case |
HsApp (XApp p) (LHsExpr p) (LHsExpr p) | Application |
HsAppType (XAppTypeE p) (LHsExpr p) !(LHsToken "@" 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 |
HsPar |
|
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 SumWidth (LHsExpr p) | Used for unboxed sum types
There will be multiple |
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) !(LHsToken "let" p) (HsLocalBinds p) !(LHsToken "in" p) (LHsExpr p) | let(rec)
|
HsDo (XDo p) HsDoFlavour (XRec p [ExprLStmt p]) | |
ExplicitList (XExplicitList p) [LHsExpr p] | Syntactic list: [a,b,c,...]
|
RecordCon | Record construction
|
Fields
| |
RecordUpd | Record update |
Fields
| |
HsGetField | Record field selection e.g |
HsProjection | Record field selector. e.g. This case only arises when the OverloadedRecordDot langauge extensions is enabled. See Note [Record selectors in the AST]. |
Fields
| |
ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p)) | Expression with an explicit type signature. |
ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p) | Arithmetic sequence
|
HsTypedBracket (XTypedBracket p) (LHsExpr p) | |
HsUntypedBracket (XUntypedBracket p) (HsQuote p) | |
HsTypedSplice (XTypedSplice p) (LHsExpr p) | |
HsUntypedSplice (XUntypedSplice p) (HsUntypedSplice p) | |
HsProc (XProc p) (LPat p) (LHsCmdTop p) |
|
HsStatic (XStatic p) (LHsExpr p) | |
HsPragE (XPragE p) (HsPragE p) (LHsExpr p) | |
XExpr !(XXExpr p) |
Instances
data HsMatchContext p #
Haskell Match Context
Context of a pattern match. This is more subtle than it would seem. See Note [FunBind vs PatBind].
Constructors
FunRhs | A pattern matching on an argument of a function binding |
Fields
| |
LambdaExpr | Patterns of a lambda |
CaseAlt | Patterns and guards in a case alternative |
LamCaseAlt LamCaseVariant | Patterns and guards in |
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
HsDoStmt HsDoFlavour | Context for HsDo (do-notation and comprehensions) |
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 |
ArrowExpr | do-notation in an arrow-command context |
Instances
data MatchGroup p body #
Constructors
MG | |
XMatchGroup !(XXMatchGroup p body) |
Instances
ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Entry # setAnnotationAnchor :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Anchor -> EpAnnComments -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> EP w m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # | |
ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Entry # setAnnotationAnchor :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Anchor -> EpAnnComments -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> EP w m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # |
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 | |
ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR)) |
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 | |
RecStmt | |
Fields
| |
XStmtLR !(XXStmtLR idL idR body) |
Instances
HsSyn / GHC.Hs
Instances
Data Fixity | |
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 | |
Outputable Fixity | |
Defined in GHC.Types.Fixity | |
Eq Fixity | |
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., |
AnyclassStrategy (XAnyClassStrategy pass) | -XDeriveAnyClass |
NewtypeStrategy (XNewtypeStrategy pass) | -XGeneralizedNewtypeDeriving |
ViaStrategy (XViaStrategy pass) | -XDerivingVia |
Instances
ExactPrint (DerivStrategy GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: DerivStrategy GhcPs -> Entry # setAnnotationAnchor :: DerivStrategy GhcPs -> Anchor -> EpAnnComments -> DerivStrategy GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DerivStrategy GhcPs -> EP w m (DerivStrategy GhcPs) # | |
type Anno (DerivStrategy (GhcPass p)) | |
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
]"
Constructors
InjectivityAnn (XCInjectivityAnn pass) (LIdP pass) [LIdP pass] | |
XInjectivityAnn !(XXInjectivityAnn pass) |
Instances
ExactPrint (InjectivityAnn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: InjectivityAnn GhcPs -> Entry # setAnnotationAnchor :: InjectivityAnn GhcPs -> Anchor -> EpAnnComments -> InjectivityAnn GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => InjectivityAnn GhcPs -> EP w m (InjectivityAnn GhcPs) # | |
type Anno (InjectivityAnn (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Rule Binder
Constructors
RuleBndr (XCRuleBndr pass) (LIdP pass) | |
RuleBndrSig (XRuleBndrSig pass) (LIdP pass) (HsPatSigType pass) | |
XRuleBndr !(XXRuleBndr pass) |
Instances
ExactPrint (FunDep GhcPs) | |
type Anno (FunDep (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Instances
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 | |
AnnBang |
|
AnnBackquote | '`' |
AnnBy | |
AnnCase | case or lambda case |
AnnCases | lambda cases |
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 |
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
|
AnnOpenB | '(|' |
AnnOpenBU | '(|', unicode variant |
AnnOpenC | '{' |
AnnOpenE | '[e|' or '[e||' |
AnnOpenEQ | '[|' |
AnnOpenEQU | '[|', unicode variant |
AnnOpenP | '(' |
AnnOpenS | '[' |
AnnOpenPH | '(#' |
AnnDollar | prefix |
AnnDollarDollar | prefix |
AnnPackageName | |
AnnPattern | |
AnnPercent |
|
AnnPercentOne | '%1' -- for HsLinearArrow |
AnnProc | |
AnnQualified | |
AnnRarrow |
|
AnnRarrowU |
|
AnnRec | |
AnnRole | |
AnnSafe | |
AnnSemi | ';' |
AnnSimpleQuote | ''' |
AnnSignature | |
AnnStatic |
|
AnnStock | |
AnnThen | |
AnnThTyQuote | double ''' |
AnnTilde | |
AnnType | |
AnnUnit |
|
AnnUsing | |
AnnVal | e.g. INTEGER |
AnnValStr | String value, will need quotes when output |
AnnVbar | '|' |
AnnVia |
|
AnnWhere | |
Annlarrowtail |
|
AnnlarrowtailU |
|
Annrarrowtail |
|
AnnrarrowtailU |
|
AnnLarrowtail |
|
AnnLarrowtailU |
|
AnnRarrowtail |
|
AnnRarrowtailU |
|
Instances
Annotation Declaration
Constructors
HsAnnotation (XHsAnnotation pass) (AnnProvenance pass) (XRec pass (HsExpr pass)) | |
XAnnDecl !(XXAnnDecl pass) |
Instances
ExactPrint (AnnDecl GhcPs) | |
type Anno (AnnDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Imported or exported entity.
Constructors
IEVar (XIEVar pass) (LIEWrappedName pass) | Imported or Exported Variable |
IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
IEThingAll (XIEThingAll pass) (LIEWrappedName 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 pass) IEWildcard [LIEWrappedName 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]
- |
IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName) | Imported or exported module contents (Export Only) |
IEGroup (XIEGroup pass) Int (LHsDoc pass) | Doc section heading |
IEDoc (XIEDoc pass) (LHsDoc pass) | Some documentation |
IEDocNamed (XIEDocNamed pass) String | Reference to named doc |
XIE !(XXIE pass) |
Instances
ExactPrint (LocatedL [LocatedA (IE GhcPs)]) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: LocatedL [LocatedA (IE GhcPs)] -> Entry # setAnnotationAnchor :: LocatedL [LocatedA (IE GhcPs)] -> Anchor -> EpAnnComments -> LocatedL [LocatedA (IE GhcPs)] # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedL [LocatedA (IE GhcPs)] -> EP w m (LocatedL [LocatedA (IE GhcPs)]) # | |
ExactPrint (IE GhcPs) | |
type Anno (LocatedA (IE (GhcPass p))) | |
Defined in GHC.Hs.ImpExp | |
type Anno (IE (GhcPass p)) | |
Defined in GHC.Hs.ImpExp | |
type Anno [LocatedA (IE (GhcPass p))] | |
Defined in GHC.Hs.ImpExp |
A Haskell expression.
Constructors
HsVar (XVar p) (LIdP p) | Variable See Note [Located RdrNames] |
HsUnboundVar (XUnboundVar p) RdrName | 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. |
HsRecSel (XRecSel p) (FieldOcc p) | Variable pointing to record selector See Note [Non-overloaded record field selectors] and Note [Record selectors in the AST] |
HsOverLabel (XOverLabel p) SourceText FastString | Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels) Note [Pragma source text] in GHC.Types.SourceText |
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) LamCaseVariant (MatchGroup p (LHsExpr p)) | Lambda-case |
HsApp (XApp p) (LHsExpr p) (LHsExpr p) | Application |
HsAppType (XAppTypeE p) (LHsExpr p) !(LHsToken "@" 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 |
HsPar |
|
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 SumWidth (LHsExpr p) | Used for unboxed sum types
There will be multiple |
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) !(LHsToken "let" p) (HsLocalBinds p) !(LHsToken "in" p) (LHsExpr p) | let(rec)
|
HsDo (XDo p) HsDoFlavour (XRec p [ExprLStmt p]) | |
ExplicitList (XExplicitList p) [LHsExpr p] | Syntactic list: [a,b,c,...]
|
RecordCon | Record construction
|
Fields
| |
RecordUpd | Record update |
Fields
| |
HsGetField | Record field selection e.g |
HsProjection | Record field selector. e.g. This case only arises when the OverloadedRecordDot langauge extensions is enabled. See Note [Record selectors in the AST]. |
Fields
| |
ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p)) | Expression with an explicit type signature. |
ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p) | Arithmetic sequence
|
HsTypedBracket (XTypedBracket p) (LHsExpr p) | |
HsUntypedBracket (XUntypedBracket p) (HsQuote p) | |
HsTypedSplice (XTypedSplice p) (LHsExpr p) | |
HsUntypedSplice (XUntypedSplice p) (HsUntypedSplice p) | |
HsProc (XProc p) (LPat p) (LHsCmdTop p) |
|
HsStatic (XStatic p) (LHsExpr p) | |
HsPragE (XPragE p) (HsPragE p) (LHsExpr p) | |
XExpr !(XXExpr p) |
Instances
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 DataConCantHappen
, 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
Data NoExtField | |
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 # | |
Eq NoExtField | |
Defined in Language.Haskell.Syntax.Extension | |
Ord NoExtField | |
Defined in Language.Haskell.Syntax.Extension Methods compare :: NoExtField -> NoExtField -> Ordering # (<) :: NoExtField -> NoExtField -> Bool # (<=) :: NoExtField -> NoExtField -> Bool # (>) :: NoExtField -> NoExtField -> Bool # (>=) :: NoExtField -> NoExtField -> Bool # max :: NoExtField -> NoExtField -> NoExtField # min :: NoExtField -> NoExtField -> NoExtField # |
data SrcUnpackedness #
Source Unpackedness
What unpackedness the user requested
Constructors
SrcUnpack | {-# UNPACK #-} specified |
SrcNoUnpack | {-# NOUNPACK #-} specified |
NoSrcUnpack | no unpack pragma |
Instances
Data SrcUnpackedness | |
Defined in Language.Haskell.Syntax.Basic 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 # | |
Eq SrcUnpackedness | |
Defined in Language.Haskell.Syntax.Basic Methods (==) :: SrcUnpackedness -> SrcUnpackedness -> Bool # (/=) :: SrcUnpackedness -> SrcUnpackedness -> Bool # |
data SrcStrictness #
Source Strictness
What strictness annotation the user wrote
Constructors
SrcLazy | Lazy, ie |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
Instances
Data SrcStrictness | |
Defined in Language.Haskell.Syntax.Basic 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 # | |
Eq SrcStrictness | |
Defined in Language.Haskell.Syntax.Basic Methods (==) :: SrcStrictness -> SrcStrictness -> Bool # (/=) :: SrcStrictness -> SrcStrictness -> Bool # |
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
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] |
Defined in GHC.Hs.Extension |
type family XXIEWrappedName p #
Instances
type XXIEWrappedName (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEType (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEPattern p #
Instances
type XIEPattern (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEName (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XXIE (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEDocNamed x #
Instances
type XIEDocNamed (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEDoc (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEGroup (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEModuleContents x #
Instances
type XIEModuleContents GhcPs | |
Defined in GHC.Hs.ImpExp | |
type XIEModuleContents GhcRn | |
Defined in GHC.Hs.ImpExp | |
type XIEModuleContents GhcTc | |
Defined in GHC.Hs.ImpExp |
type family XIEThingWith x #
Instances
type XIEThingWith (GhcPass 'Parsed) | |
Defined in GHC.Hs.ImpExp | |
type XIEThingWith (GhcPass 'Renamed) | |
Defined in GHC.Hs.ImpExp | |
type XIEThingWith (GhcPass 'Typechecked) | |
Defined in GHC.Hs.ImpExp |
type family XIEThingAll x #
Instances
type XIEThingAll (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEThingAbs x #
Instances
type XIEThingAbs (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEVar GhcPs | |
Defined in GHC.Hs.ImpExp | |
type XIEVar GhcRn | |
Defined in GHC.Hs.ImpExp | |
type XIEVar GhcTc | |
Defined in GHC.Hs.ImpExp |
type family ImportDeclPkgQual x #
Instances
type ImportDeclPkgQual GhcPs | |
Defined in GHC.Hs.ImpExp | |
type ImportDeclPkgQual GhcRn | |
Defined in GHC.Hs.ImpExp | |
type ImportDeclPkgQual GhcTc | |
Defined in GHC.Hs.ImpExp |
type family XXImportDecl x #
Instances
type XXImportDecl (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XCImportDecl x #
Instances
type XCImportDecl GhcPs | |
Defined in GHC.Hs.ImpExp | |
type XCImportDecl GhcRn | |
Defined in GHC.Hs.ImpExp | |
type XCImportDecl GhcTc | |
Defined in GHC.Hs.ImpExp |
type family XXFieldOcc x #
Instances
type XXFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XCFieldOcc x #
Instances
type XCFieldOcc GhcPs | |
Defined in GHC.Hs.Type | |
type XCFieldOcc GhcRn | |
Defined in GHC.Hs.Type | |
type XCFieldOcc GhcTc | |
Defined in GHC.Hs.Type |
type family XXConDeclField x #
Instances
type XXConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XConDeclField x #
Instances
type XConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XXTyVarBndr x #
Instances
type XXTyVarBndr (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XKindedTyVar x #
Instances
type XKindedTyVar (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XUserTyVar x #
Instances
type XUserTyVar (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XXHsForAllTelescope x #
Instances
type XXHsForAllTelescope (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XHsForAllInvis x #
Instances
type XHsForAllInvis (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XHsForAllVis x #
Instances
type XHsForAllVis (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XXTyLit (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XCharTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XStrTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XNumTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XWildCardTy x #
Instances
type XWildCardTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XTyLit (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XExplicitTupleTy x #
Instances
type XExplicitTupleTy GhcPs | |
Defined in GHC.Hs.Type | |
type XExplicitTupleTy GhcRn | |
Defined in GHC.Hs.Type | |
type XExplicitTupleTy GhcTc | |
Defined in GHC.Hs.Type |
type family XExplicitListTy x #
Instances
type XExplicitListTy GhcPs | |
Defined in GHC.Hs.Type | |
type XExplicitListTy GhcRn | |
Defined in GHC.Hs.Type | |
type XExplicitListTy GhcTc | |
Defined in GHC.Hs.Type |
Instances
type XRecTy GhcPs | |
Defined in GHC.Hs.Type | |
type XRecTy GhcRn | |
Defined in GHC.Hs.Type | |
type XRecTy GhcTc | |
Defined in GHC.Hs.Type |
Instances
type XSpliceTy GhcPs | |
Defined in GHC.Hs.Type | |
type XSpliceTy GhcRn | |
Defined in GHC.Hs.Type | |
type XSpliceTy GhcTc | |
Defined in GHC.Hs.Type |
Instances
type XStarTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XAppKindTy x #
Instances
type XAppKindTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XAppTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XQualTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XForAllTy (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XXHsPatSigType x #
Instances
type XXHsPatSigType (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XXHsWildCardBndrs x b #
Instances
type XXHsWildCardBndrs (GhcPass _1) _2 | |
Defined in GHC.Hs.Type |
Instances
type XHsWC GhcPs b | |
Defined in GHC.Hs.Type | |
type XHsWC GhcRn b | |
Defined in GHC.Hs.Type | |
type XHsWC GhcTc b | |
Defined in GHC.Hs.Type |
type family XXHsSigType x #
Instances
type XXHsSigType (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XHsSig (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XXHsOuterTyVarBndrs x #
Instances
type XXHsOuterTyVarBndrs (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XHsOuterExplicit x flag #
Instances
type XHsOuterExplicit GhcPs _1 | |
Defined in GHC.Hs.Type | |
type XHsOuterExplicit GhcRn _1 | |
Defined in GHC.Hs.Type | |
type XHsOuterExplicit GhcTc flag | |
Defined in GHC.Hs.Type |
type family XHsOuterImplicit x #
Instances
type XHsOuterImplicit GhcPs | |
Defined in GHC.Hs.Type | |
type XHsOuterImplicit GhcRn | |
Defined in GHC.Hs.Type | |
type XHsOuterImplicit GhcTc | |
Defined in GHC.Hs.Type |
type family XXLHsQTyVars x #
Instances
type XXLHsQTyVars (GhcPass _1) | |
Defined in GHC.Hs.Type |
Instances
type XHsQTvs GhcPs | |
Defined in GHC.Hs.Type | |
type XHsQTvs GhcRn | |
Defined in GHC.Hs.Type | |
type XHsQTvs GhcTc | |
Defined in GHC.Hs.Type |
type family XHsFieldBind x #
Instances
type XHsFieldBind _1 | |
Defined in GHC.Hs.Pat |
Instances
type XXPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XXPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XXPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XSigPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcTc | |
Defined in GHC.Hs.Pat |
type family XNPlusKPat x #
Instances
type XNPlusKPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XLitPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
type family XSplicePat x #
Instances
type XSplicePat GhcPs | |
Defined in GHC.Hs.Pat | |
type XSplicePat GhcRn | |
Defined in GHC.Hs.Pat | |
type XSplicePat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XConPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XConPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XConPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XSumPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XTuplePat GhcPs | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcRn | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XListPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XListPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XListPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XBangPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XBangPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XBangPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XAsPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XAsPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XAsPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XLazyPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XLazyPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XLazyPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XVarPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XWildPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XXOverLit (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XOverLit GhcPs | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcRn | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcTc | |
Defined in GHC.Hs.Lit |
Instances
type XXLit (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsDoublePrim x #
Instances
type XHsDoublePrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsFloatPrim x #
Instances
type XHsFloatPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsRat (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsInteger x #
Instances
type XHsInteger (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsWord64Prim x #
Instances
type XHsWord64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsInt64Prim x #
Instances
type XHsInt64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsWordPrim x #
Instances
type XHsWordPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsIntPrim x #
Instances
type XHsIntPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsInt (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsStringPrim x #
Instances
type XHsStringPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsString (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsCharPrim x #
Instances
type XHsCharPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsChar (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XXApplicativeArg x #
Instances
type XXApplicativeArg (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XApplicativeArgMany x #
Instances
type XApplicativeArgMany (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XApplicativeArgOne x #
Instances
type XApplicativeArgOne GhcPs | |
Defined in GHC.Hs.Expr | |
type XApplicativeArgOne GhcRn | |
Defined in GHC.Hs.Expr | |
type XApplicativeArgOne GhcTc | |
Defined in GHC.Hs.Expr |
type family XXParStmtBlock x x' #
Instances
type XXParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr |
type family XParStmtBlock x x' #
Instances
type XParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr |
Instances
type XXCmd GhcPs | |
Defined in GHC.Hs.Expr | |
type XXCmd GhcRn | |
Defined in GHC.Hs.Expr | |
type XXCmd GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCmdWrap (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdDo GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCmdLet GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdLet GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdLet GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCmdIf GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdIf GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdIf GhcTc | |
Defined in GHC.Hs.Expr |
type family XCmdLamCase x #
Instances
type XCmdLamCase (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdCase GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdCase GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdCase GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCmdLam (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XCmdArrForm x #
Instances
type XCmdArrForm GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdArrForm GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdArrForm GhcTc | |
Defined in GHC.Hs.Expr |
type family XCmdArrApp x #
Instances
type XCmdArrApp GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XXStmtLR (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr |
type family XTransStmt x x' b #
Instances
type XTransStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr |
Instances
type XParStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr |
type family XBodyStmt x x' b #
Instances
type XBodyStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr |
type family XApplicativeStmt x x' b #
Instances
type XApplicativeStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr |
type family XLastStmt x x' b #
Instances
type XLastStmt (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr |
Instances
type XXGRHS (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
Instances
type XXGRHSs (GhcPass _1) _2 | |
Defined in GHC.Hs.Expr |
Instances
type XCGRHSs (GhcPass _1) _2 | |
Defined in GHC.Hs.Expr |
Instances
type XXMatch (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
type family XXMatchGroup x b #
Instances
type XXMatchGroup (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
Instances
type XMG GhcPs b | |
Defined in GHC.Hs.Expr | |
type XMG GhcRn b | |
Defined in GHC.Hs.Expr | |
type XMG GhcTc b | |
Defined in GHC.Hs.Expr |
Instances
type XXCmdTop (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdTop GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XXQuote GhcPs | |
Defined in GHC.Hs.Expr | |
type XXQuote GhcRn | |
Defined in GHC.Hs.Expr | |
type XXQuote GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XVarBr GhcPs | |
Defined in GHC.Hs.Expr | |
type XVarBr GhcRn | |
Defined in GHC.Hs.Expr | |
type XVarBr GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XTypBr GhcPs | |
Defined in GHC.Hs.Expr | |
type XTypBr GhcRn | |
Defined in GHC.Hs.Expr | |
type XTypBr GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XDecBrG GhcPs | |
Defined in GHC.Hs.Expr | |
type XDecBrG GhcRn | |
Defined in GHC.Hs.Expr | |
type XDecBrG GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XDecBrL GhcPs | |
Defined in GHC.Hs.Expr | |
type XDecBrL GhcRn | |
Defined in GHC.Hs.Expr | |
type XDecBrL GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XPatBr GhcPs | |
Defined in GHC.Hs.Expr | |
type XPatBr GhcRn | |
Defined in GHC.Hs.Expr | |
type XPatBr GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XExpBr GhcPs | |
Defined in GHC.Hs.Expr | |
type XExpBr GhcRn | |
Defined in GHC.Hs.Expr | |
type XExpBr GhcTc | |
Defined in GHC.Hs.Expr |
type family XXUntypedSplice x #
Instances
type XXUntypedSplice p | |
Defined in GHC.Hs.Expr |
type family XQuasiQuote x #
Instances
type XQuasiQuote p | |
Defined in GHC.Hs.Expr |
type family XUntypedSpliceExpr x #
Instances
type XUntypedSpliceExpr GhcPs | |
Defined in GHC.Hs.Expr | |
type XUntypedSpliceExpr GhcRn | |
Defined in GHC.Hs.Expr | |
type XUntypedSpliceExpr GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XXTupArg (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XMissing GhcPs | |
Defined in GHC.Hs.Expr | |
type XMissing GhcRn | |
Defined in GHC.Hs.Expr | |
type XMissing GhcTc | |
Defined in GHC.Hs.Expr |
type family XXAmbiguousFieldOcc x #
Instances
type XXAmbiguousFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Type |
type family XAmbiguous x #
Instances
type XAmbiguous GhcPs | |
Defined in GHC.Hs.Type | |
type XAmbiguous GhcRn | |
Defined in GHC.Hs.Type | |
type XAmbiguous GhcTc | |
Defined in GHC.Hs.Type |
type family XUnambiguous x #
Instances
type XUnambiguous GhcPs | |
Defined in GHC.Hs.Type | |
type XUnambiguous GhcRn | |
Defined in GHC.Hs.Type | |
type XUnambiguous GhcTc | |
Defined in GHC.Hs.Type |
Instances
type XXPragE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XSCC (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XXDotFieldOcc x #
Instances
type XXDotFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XCDotFieldOcc x #
Instances
type XCDotFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XXExpr GhcPs | |
Defined in GHC.Hs.Expr | |
type XXExpr GhcRn | |
Defined in GHC.Hs.Expr | |
type XXExpr GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XPragE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XUntypedSplice x #
Instances
type XUntypedSplice GhcPs | |
Defined in GHC.Hs.Expr | |
type XUntypedSplice GhcRn | |
Defined in GHC.Hs.Expr | |
type XUntypedSplice GhcTc | |
Defined in GHC.Hs.Expr |
type family XTypedSplice x #
Instances
type XTypedSplice GhcPs | |
Defined in GHC.Hs.Expr | |
type XTypedSplice GhcRn | |
Defined in GHC.Hs.Expr | |
type XTypedSplice GhcTc | |
Defined in GHC.Hs.Expr |
type family XUntypedBracket x #
Instances
type XUntypedBracket GhcPs | |
Defined in GHC.Hs.Expr | |
type XUntypedBracket GhcRn | |
Defined in GHC.Hs.Expr | |
type XUntypedBracket GhcTc | |
Defined in GHC.Hs.Expr |
type family XTypedBracket x #
Instances
type XTypedBracket GhcPs | |
Defined in GHC.Hs.Expr | |
type XTypedBracket GhcRn | |
Defined in GHC.Hs.Expr | |
type XTypedBracket GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XArithSeq GhcPs | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcRn | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcTc | |
Defined in GHC.Hs.Expr |
type family XExprWithTySig x #
Instances
type XExprWithTySig GhcPs | |
Defined in GHC.Hs.Expr | |
type XExprWithTySig GhcRn | |
Defined in GHC.Hs.Expr | |
type XExprWithTySig GhcTc | |
Defined in GHC.Hs.Expr |
type family XProjection x #
Instances
type XProjection GhcPs | |
Defined in GHC.Hs.Expr | |
type XProjection GhcRn | |
Defined in GHC.Hs.Expr | |
type XProjection GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XGetField GhcPs | |
Defined in GHC.Hs.Expr | |
type XGetField GhcRn | |
Defined in GHC.Hs.Expr | |
type XGetField GhcTc | |
Defined in GHC.Hs.Expr |
type family XRecordUpd x #
Instances
type XRecordUpd GhcPs | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcRn | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcTc | |
Defined in GHC.Hs.Expr |
type family XRecordCon x #
Instances
type XRecordCon GhcPs | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcRn | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcTc | |
Defined in GHC.Hs.Expr |
type family XExplicitList x #
Instances
type XExplicitList GhcPs | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcRn | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XDo GhcPs | |
Defined in GHC.Hs.Expr | |
type XDo GhcRn | |
Defined in GHC.Hs.Expr | |
type XDo GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XLet GhcPs | |
Defined in GHC.Hs.Expr | |
type XLet GhcRn | |
Defined in GHC.Hs.Expr | |
type XLet GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XMultiIf GhcPs | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcRn | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XIf GhcPs | |
Defined in GHC.Hs.Expr | |
type XIf GhcRn | |
Defined in GHC.Hs.Expr | |
type XIf GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCase GhcPs | |
Defined in GHC.Hs.Expr | |
type XCase GhcRn | |
Defined in GHC.Hs.Expr | |
type XCase GhcTc | |
Defined in GHC.Hs.Expr |
type family XExplicitSum x #
Instances
type XExplicitSum GhcPs | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcRn | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcTc | |
Defined in GHC.Hs.Expr |
type family XExplicitTuple x #
Instances
type XExplicitTuple GhcPs | |
Defined in GHC.Hs.Expr | |
type XExplicitTuple GhcRn | |
Defined in GHC.Hs.Expr | |
type XExplicitTuple GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XSectionR GhcPs | |
Defined in GHC.Hs.Expr | |
type XSectionR GhcRn | |
Defined in GHC.Hs.Expr | |
type XSectionR GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XSectionL GhcPs | |
Defined in GHC.Hs.Expr | |
type XSectionL GhcRn | |
Defined in GHC.Hs.Expr | |
type XSectionL GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XNegApp GhcPs | |
Defined in GHC.Hs.Expr | |
type XNegApp GhcRn | |
Defined in GHC.Hs.Expr | |
type XNegApp GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XOpApp GhcPs | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcRn | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XAppTypeE GhcPs | |
Defined in GHC.Hs.Expr | |
type XAppTypeE GhcRn | |
Defined in GHC.Hs.Expr | |
type XAppTypeE GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XLam (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type XLam (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XIPVar GhcPs | |
Defined in GHC.Hs.Expr | |
type XIPVar GhcRn | |
Defined in GHC.Hs.Expr | |
type XIPVar GhcTc | |
Defined in GHC.Hs.Expr |
type family XOverLabel x #
Instances
type XOverLabel GhcPs | |
Defined in GHC.Hs.Expr | |
type XOverLabel GhcRn | |
Defined in GHC.Hs.Expr | |
type XOverLabel GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XRecSel GhcPs | |
Defined in GHC.Hs.Expr | |
type XRecSel GhcRn | |
Defined in GHC.Hs.Expr | |
type XRecSel GhcTc | |
Defined in GHC.Hs.Expr |
type family XUnboundVar x #
Instances
type XUnboundVar GhcPs | |
Defined in GHC.Hs.Expr | |
type XUnboundVar GhcRn | |
Defined in GHC.Hs.Expr | |
type XUnboundVar GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XVar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type XVar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XXInjectivityAnn x #
Instances
type XXInjectivityAnn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCInjectivityAnn x #
Instances
type XCInjectivityAnn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXRoleAnnotDecl x #
Instances
type XXRoleAnnotDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCRoleAnnotDecl x #
Instances
type XCRoleAnnotDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XCRoleAnnotDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XCRoleAnnotDecl GhcTc | |
Defined in GHC.Hs.Decls |
Instances
type XXAnnDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XHsAnnotation x #
Instances
type XHsAnnotation (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXWarnDecl x #
Instances
type XXWarnDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXWarnDecls x #
Instances
type XXWarnDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XWarnings GhcPs | |
Defined in GHC.Hs.Decls | |
type XWarnings GhcRn | |
Defined in GHC.Hs.Decls | |
type XWarnings GhcTc | |
Defined in GHC.Hs.Decls |
type family XXRuleBndr x #
Instances
type XXRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XRuleBndrSig x #
Instances
type XRuleBndrSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCRuleBndr x #
Instances
type XCRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXRuleDecl x #
Instances
type XXRuleDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XHsRule GhcPs | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcRn | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcTc | |
Defined in GHC.Hs.Decls |
type family XXRuleDecls x #
Instances
type XXRuleDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCRuleDecls x #
Instances
type XCRuleDecls GhcPs | |
Defined in GHC.Hs.Decls | |
type XCRuleDecls GhcRn | |
Defined in GHC.Hs.Decls | |
type XCRuleDecls GhcTc | |
Defined in GHC.Hs.Decls |
type family XXForeignExport x #
Instances
type XXForeignExport (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XCExport (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXForeignImport x #
Instances
type XXForeignImport (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XCImport (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXForeignDecl x #
Instances
type XXForeignDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XForeignExport x #
Instances
type XForeignExport GhcPs | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcRn | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcTc | |
Defined in GHC.Hs.Decls |
type family XForeignImport x #
Instances
type XForeignImport GhcPs | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcRn | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcTc | |
Defined in GHC.Hs.Decls |
type family XXDefaultDecl x #
Instances
type XXDefaultDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCDefaultDecl x #
Instances
type XCDefaultDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XCDefaultDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XCDefaultDecl GhcTc | |
Defined in GHC.Hs.Decls |
type family XViaStrategy x #
Instances
type XViaStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcTc | |
Defined in GHC.Hs.Decls |
type family XNewtypeStrategy x #
Instances
type XNewtypeStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
type XNewtypeStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
type XNewtypeStrategy GhcTc | |
Defined in GHC.Hs.Decls |
type family XAnyClassStrategy x #
Instances
type XAnyClassStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
type XAnyClassStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
type XAnyClassStrategy GhcTc | |
Defined in GHC.Hs.Decls |
type family XStockStrategy x #
Instances
type XStockStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
type XStockStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
type XStockStrategy GhcTc | |
Defined in GHC.Hs.Decls |
type family XXDerivDecl x #
Instances
type XXDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCDerivDecl x #
Instances
type XCDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXInstDecl x #
Instances
type XXInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XTyFamInstD x #
Instances
type XTyFamInstD GhcPs | |
Defined in GHC.Hs.Decls | |
type XTyFamInstD GhcRn | |
Defined in GHC.Hs.Decls | |
type XTyFamInstD GhcTc | |
Defined in GHC.Hs.Decls |
type family XDataFamInstD x #
Instances
type XDataFamInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XClsInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXClsInstDecl x #
Instances
type XXClsInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCClsInstDecl x #
Instances
type XCClsInstDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XCClsInstDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XCClsInstDecl GhcTc | |
Defined in GHC.Hs.Decls |
type family XXTyFamInstDecl x #
Instances
type XXTyFamInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCTyFamInstDecl x #
Instances
type XCTyFamInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XXFamEqn (GhcPass _1) r | |
Defined in GHC.Hs.Decls |
Instances
type XXConDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XConDeclH98 x #
Instances
type XConDeclH98 (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XConDeclGADT x #
Instances
type XConDeclGADT (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXDerivClauseTys x #
Instances
type XXDerivClauseTys (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDctMulti (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XDctSingle x #
Instances
type XDctSingle (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXHsDerivingClause x #
Instances
type XXHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCHsDerivingClause x #
Instances
type XCHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXHsDataDefn x #
Instances
type XXHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCHsDataDefn x #
Instances
type XCHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXFamilyDecl x #
Instances
type XXFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCFamilyDecl x #
Instances
type XCFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXFamilyResultSig x #
Instances
type XXFamilyResultSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XTyVarSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XCKindSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XNoSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXTyClGroup x #
Instances
type XXTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XCTyClGroup x #
Instances
type XCTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XXFunDep (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXTyClDecl x #
Instances
type XXTyClDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XClassDecl x #
Instances
type XClassDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcTc | |
Defined in GHC.Hs.Decls |
Instances
type XDataDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcTc | |
Defined in GHC.Hs.Decls |
Instances
type XFamDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXSpliceDecl x #
Instances
type XXSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XSpliceDecl x #
Instances
type XSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XXHsGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XCHsGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XXHsDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XRoleAnnotD x #
Instances
type XRoleAnnotD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDocD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XSpliceD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XRuleD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XAnnD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XWarningD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XForD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDefD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XKindSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XValD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDerivD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XTyClD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXStandaloneKindSig x #
Instances
type XXStandaloneKindSig (GhcPass p) | |
Defined in GHC.Hs.Decls |
type family XStandaloneKindSig x #
Instances
type XStandaloneKindSig GhcPs | |
Defined in GHC.Hs.Decls | |
type XStandaloneKindSig GhcRn | |
Defined in GHC.Hs.Decls | |
type XStandaloneKindSig GhcTc | |
Defined in GHC.Hs.Decls |
type family XXFixitySig x #
Instances
type XXFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XFixitySig x #
Instances
type XFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XXSig GhcPs | |
Defined in GHC.Hs.Binds | |
type XXSig GhcRn | |
Defined in GHC.Hs.Binds | |
type XXSig GhcTc | |
Defined in GHC.Hs.Binds |
type family XCompleteMatchSig x #
Instances
type XCompleteMatchSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XSCCFunSig x #
Instances
type XSCCFunSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XMinimalSig x #
Instances
type XMinimalSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XSpecInstSig x #
Instances
type XSpecInstSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XInlineSig x #
Instances
type XInlineSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XClassOpSig x #
Instances
type XClassOpSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XPatSynSig x #
Instances
type XPatSynSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XXIPBind (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XCIPBind GhcPs | |
Defined in GHC.Hs.Binds | |
type XCIPBind GhcRn | |
Defined in GHC.Hs.Binds | |
type XCIPBind GhcTc | |
Defined in GHC.Hs.Binds |
type family XXHsIPBinds x #
Instances
type XXHsIPBinds (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XIPBinds GhcPs | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcRn | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcTc | |
Defined in GHC.Hs.Binds |
type family XXPatSynBind x x' #
Instances
type XXPatSynBind (GhcPass idL) (GhcPass idR) | |
Defined in GHC.Hs.Binds |
Instances
type family XXHsBindsLR x x' #
Instances
type XXHsBindsLR GhcPs pR | |
Defined in GHC.Hs.Binds | |
type XXHsBindsLR GhcRn pR | |
Defined in GHC.Hs.Binds | |
type XXHsBindsLR GhcTc pR | |
Defined in GHC.Hs.Binds |
type family XPatSynBind x x' #
Instances
type XPatSynBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
Instances
type XVarBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
Instances
type XFunBind (GhcPass pL) GhcPs | |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcRn | After the renamer (but before the type-checker), the FunBind extension field contains the locally-bound free variables of this defn. See Note [Bind free vars] |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcTc | After the type-checker, the FunBind extension field contains the ticks to put on the rhs, if any, and 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'. |
Defined in GHC.Hs.Binds |
type family XXValBindsLR x x' #
Instances
type XXValBindsLR (GhcPass pL) pR | |
Defined in GHC.Hs.Binds |
Instances
type XValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XXHsLocalBindsLR x x' #
Instances
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XEmptyLocalBinds x x' #
Instances
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XHsIPBinds x x' #
Instances
type XHsIPBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XHsValBinds x x' #
Instances
type XHsValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
Maps the "normal" id type for a given pass
The trivial wrapper that carries no additional information See Note [XRec and SrcSpans in the AST]
We can map over the underlying type contained in an XRec
while preserving
the annotation as is.
We can strip off the XRec to access the underlying data. See Note [XRec and SrcSpans in the AST]
type family Anno a = (b :: Type) #
Instances
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
type XRec (GhcPass p) a | |
Defined in GHC.Hs.Extension |
data DataConCantHappen #
Instances
newtype ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Constructors
ModuleName FastString |
Instances
data IsBootInterface #
Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.
Instances
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 LayoutInfo pass #
Layout information for declarations.
Constructors
ExplicitBraces !(LHsToken "{" pass) !(LHsToken "}" pass) | Explicit braces written by the user. class C a where { foo :: a; bar :: a } |
VirtualBraces | Virtual braces inserted by the layout algorithm. class C a where foo :: a bar :: a |
Fields
| |
NoLayoutInfo | Empty or compiler-generated blocks do not have layout information associated with them. |
Instances
Typeable p => Data (LayoutInfo (GhcPass p)) | |
Defined in GHC.Hs.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayoutInfo (GhcPass p) -> c (LayoutInfo (GhcPass p)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LayoutInfo (GhcPass p)) # toConstr :: LayoutInfo (GhcPass p) -> Constr # dataTypeOf :: LayoutInfo (GhcPass p) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LayoutInfo (GhcPass p))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LayoutInfo (GhcPass p))) # gmapT :: (forall b. Data b => b -> b) -> LayoutInfo (GhcPass p) -> LayoutInfo (GhcPass p) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r # gmapQ :: (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) # |
data HsUniToken (tok :: Symbol) (utok :: Symbol) #
With UnicodeSyntax
, there might be multiple ways to write the same
token. For example an arrow could be either ->
or →
. This choice must be
recorded in order to exactprint such tokens, so instead of HsToken "->"
we
introduce HsUniToken "->" "→"
.
See also IsUnicodeSyntax
in GHC.Parser.Annotation
; we do not use here to
avoid a dependency.
Constructors
HsNormalTok | |
HsUnicodeTok |
Instances
(KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) | |
Defined in Language.Haskell.Syntax.Concrete Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUniToken tok utok -> c (HsUniToken tok utok) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUniToken tok utok) # toConstr :: HsUniToken tok utok -> Constr # dataTypeOf :: HsUniToken tok utok -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUniToken tok utok)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUniToken tok utok)) # gmapT :: (forall b. Data b => b -> b) -> HsUniToken tok utok -> HsUniToken tok utok # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r # gmapQ :: (forall d. Data d => d -> u) -> HsUniToken tok utok -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUniToken tok utok -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) # | |
type Anno (HsUniToken tok utok) | |
Defined in GHC.Hs.Extension |
data HsToken (tok :: Symbol) #
A token stored in the syntax tree. For example, when parsing a
let-expression, we store HsToken "let"
and HsToken "in"
.
The locations of those tokens can be used to faithfully reproduce
(exactprint) the original program text.
Constructors
HsTok |
Instances
KnownSymbol tok => Data (HsToken tok) | |
Defined in Language.Haskell.Syntax.Concrete Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsToken tok -> c (HsToken tok) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsToken tok) # toConstr :: HsToken tok -> Constr # dataTypeOf :: HsToken tok -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsToken tok)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsToken tok)) # gmapT :: (forall b. Data b => b -> b) -> HsToken tok -> HsToken tok # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r # gmapQ :: (forall d. Data d => d -> u) -> HsToken tok -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsToken tok -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) # | |
type Anno (HsToken tok) | |
Defined in GHC.Hs.Extension |
type LHsUniToken (tok :: Symbol) (utok :: Symbol) p = XRec p (HsUniToken tok utok) #
newtype HsDocStringChunk #
A contiguous chunk of documentation
Constructors
HsDocStringChunk ByteString |
Instances
data HsDocStringDecorator #
Constructors
HsDocStringNext | '|' is the decorator |
HsDocStringPrevious |
|
HsDocStringNamed !String | '$string' is the decorator |
HsDocStringGroup !Int | The decorator is the given number of |
Instances
data HsDocString #
Haskell Documentation String
Rich structure to support exact printing The location around each chunk doesn't include the decorators
Constructors
MultiLineDocString !HsDocStringDecorator !(NonEmpty LHsDocStringChunk) | The first chunk is preceded by "-- decorator" and each following chunk is preceded by "--"
Example: -- | This is a docstring for |
NestedDocString !HsDocStringDecorator LHsDocStringChunk | The docstring is preceded by "{-decorator" and followed by "-}" The chunk contains balanced pairs of '{-' and '-}' |
GeneratedDocString HsDocStringChunk | A docstring generated either internally or via TH
Pretty printed with the '-- |' decorator
This is because it may contain unbalanced pairs of '{-' and '-}' and
not form a valid |
Instances
type LHsDocString = Located HsDocString #
Arguments
= XRec p (HsExpr p) | May have |
Located Haskell Expression
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
type SyntaxExpr (GhcPass p) | |
Defined in GHC.Hs.Expr |
Guarded Right-Hand Sides
GRHSs are used both for pattern bindings and for Matches
Constructors
GRHSs | |
Fields
| |
XGRHSs !(XXGRHSs p body) |
Instances
ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Entry # setAnnotationAnchor :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Anchor -> EpAnnComments -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> EP w m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # | |
ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Entry # setAnnotationAnchor :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Anchor -> EpAnnComments -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> EP w m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # |
data MatchGroup p body #
Constructors
MG | |
XMatchGroup !(XXMatchGroup p body) |
Instances
ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Entry # setAnnotationAnchor :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Anchor -> EpAnnComments -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> EP w m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # | |
ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Entry # setAnnotationAnchor :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Anchor -> EpAnnComments -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> EP w m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # |
data HsUntypedSplice id #
Haskell Splice
Constructors
HsUntypedSpliceExpr (XUntypedSpliceExpr id) (LHsExpr id) | |
HsQuasiQuote (XQuasiQuote id) (IdP id) (XRec id FastString) | |
XUntypedSplice !(XXUntypedSplice id) |
Instances
ExactPrint (HsUntypedSplice GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsUntypedSplice GhcPs -> Entry # setAnnotationAnchor :: HsUntypedSplice GhcPs -> Anchor -> EpAnnComments -> HsUntypedSplice GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsUntypedSplice GhcPs -> EP w m (HsUntypedSplice GhcPs) # | |
type Anno (HsUntypedSplice (GhcPass p)) | |
Defined in GHC.Hs.Expr |
data PromotionFlag #
Is a TyCon a promoted data constructor or just a normal type constructor?
Constructors
NotPromoted | |
IsPromoted |
Instances
Data PromotionFlag | |
Defined in Language.Haskell.Syntax.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # | |
Eq PromotionFlag | |
Defined in Language.Haskell.Syntax.Type Methods (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # |
Constructors
NoEpAnns |
Instances
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.
Constructors
NoAnnSortKey | |
AnnSortKey [RealSrcSpan] |
Instances
Data AnnSortKey | |
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 | |
Defined in GHC.Parser.Annotation Methods mempty :: AnnSortKey # mappend :: AnnSortKey -> AnnSortKey -> AnnSortKey # mconcat :: [AnnSortKey] -> AnnSortKey # | |
Semigroup AnnSortKey | |
Defined in GHC.Parser.Annotation Methods (<>) :: AnnSortKey -> AnnSortKey -> AnnSortKey # sconcat :: NonEmpty AnnSortKey -> AnnSortKey # stimes :: Integral b => b -> AnnSortKey -> AnnSortKey # | |
Outputable AnnSortKey | |
Defined in GHC.Parser.Annotation Methods ppr :: AnnSortKey -> SDoc # | |
Eq AnnSortKey | |
Defined in GHC.Parser.Annotation |
exact print annotation used for capturing the locations of annotations in pragmas.
Instances
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
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 |
Fields | |
NameAnnCommas | |
Fields | |
NameAnnBars | Used for |
Fields
| |
NameAnnOnly | Used for |
Fields | |
NameAnnRArrow | Used for |
Fields
| |
NameAnnQuote | Used for an item with a leading |
Fields | |
NameAnnTrailing | Used when adding a |
Fields
|
Instances
data AnnContext #
Exact print annotation for the Context
data type.
Constructors
AnnContext | |
Fields
|
Instances
Data AnnContext | |
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 | |
Defined in GHC.Parser.Annotation Methods ppr :: AnnContext -> SDoc # | |
ExactPrint a => ExactPrint (LocatedC a) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint |
Detail of the "brackets" used in an AnnParen
exact print annotation.
Constructors
AnnParens | '(', ')' |
AnnParensHash | '(#', '#)' |
AnnParensSquare | '[', ']' |
Instances
Data ParenType | |
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 | |
Ord ParenType | |
exact print annotation for an item having surrounding "brackets", such as tuples or lists
Constructors
AnnParen | |
Fields |
Instances
Data AnnParen | |
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 # |
Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.
Constructors
AnnList | |
Instances
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 | |
Fields
|
Instances
data TrailingAnn #
Captures the location of punctuation occurring between items, normally in a list. It is captured as a trailing annotation.
Constructors
AddSemiAnn EpaLocation | Trailing ';' |
AddCommaAnn EpaLocation | Trailing ',' |
AddVbarAnn EpaLocation | Trailing '|' |
Instances
Data TrailingAnn | |
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 | |
Defined in GHC.Parser.Annotation Methods ppr :: TrailingAnn -> SDoc # | |
Eq TrailingAnn | |
Defined in GHC.Parser.Annotation |
type LocatedAn an = GenLocated (SrcAnn an) #
General representation of a GenLocated
type carrying a
parameterised annotation type.
type SrcSpanAnnC = SrcAnn AnnContext #
type SrcSpanAnnP = SrcAnn AnnPragma #
type SrcSpanAnnL = SrcAnn AnnList #
type SrcSpanAnnN = SrcAnn NameAnn #
type SrcSpanAnnA = SrcAnn AnnListItem #
type LocatedC = GenLocated SrcSpanAnnC #
type LocatedP = GenLocated SrcSpanAnnP #
type LocatedL = GenLocated SrcSpanAnnL #
type LocatedN = GenLocated SrcSpanAnnN #
type LocatedA = GenLocated SrcSpanAnnA #
type SrcAnn ann = SrcSpanAnn' (EpAnn ann) #
We mostly use 'SrcSpanAnn'' with an 'EpAnn''
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 !a !SrcSpan |
Instances
type LEpaComment = GenLocated Anchor EpaComment #
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 occurring 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.
Constructors
EpaComments | |
Fields
| |
EpaCommentsBalanced | |
Fields
|
Instances
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.
Constructors
UnchangedAnchor | |
MovedAnchor DeltaPos |
Instances
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
Data Anchor | |
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 | |
Show Anchor | |
Outputable Anchor | |
Defined in GHC.Parser.Annotation | |
Eq Anchor | |
Ord Anchor | |
Outputable (GenLocated Anchor EpaComment) | |
Defined in GHC.Parser.Annotation Methods ppr :: GenLocated Anchor EpaComment -> SDoc # |
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 | |
EpAnnNotUsed | No Annotation for generated code, e.g. from TH, deriving, etc. |
Instances
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
Data DeltaPos | |
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 | |
Outputable DeltaPos | |
Defined in GHC.Parser.Annotation | |
Eq DeltaPos | |
Ord DeltaPos | |
Defined in GHC.Parser.Annotation |
data TokenLocation #
Tokens embedded in the AST have an EpaLocation, unless they come from generated code (e.g. by TH).
Constructors
NoTokenLoc | |
TokenLoc !EpaLocation |
Instances
Data TokenLocation | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenLocation -> c TokenLocation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenLocation # toConstr :: TokenLocation -> Constr # dataTypeOf :: TokenLocation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenLocation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenLocation) # gmapT :: (forall b. Data b => b -> b) -> TokenLocation -> TokenLocation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenLocation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenLocation -> r # gmapQ :: (forall d. Data d => d -> u) -> TokenLocation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenLocation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # | |
Eq TokenLocation | |
Defined in GHC.Parser.Annotation Methods (==) :: TokenLocation -> TokenLocation -> Bool # (/=) :: TokenLocation -> TokenLocation -> Bool # | |
Outputable a => Outputable (GenLocated TokenLocation a) | |
Defined in GHC.Parser.Annotation Methods ppr :: GenLocated TokenLocation a -> SDoc # |
data EpaLocation #
The anchor for an
. The Parser inserts the
AnnKeywordId
variant, giving the exact location of the original item
in the parsed source. This can be replaced by the EpaSpan
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.EpaDelta
Constructors
EpaSpan !RealSrcSpan !(Maybe BufSpan) | |
EpaDelta !DeltaPos ![LEpaComment] |
Instances
Data EpaLocation | |
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 | |
Defined in GHC.Parser.Annotation Methods ppr :: EpaLocation -> SDoc # | |
Eq EpaLocation | |
Defined in GHC.Parser.Annotation |
Captures an annotation, storing the
and its
location. The parser only ever inserts AnnKeywordId
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 EpaLocation
AddEpAnn
is created is using the mj
("make
jump") function, and then it can be inserted into the appropriate
annotation.
Constructors
AddEpAnn AnnKeywordId EpaLocation |
Instances
Data AddEpAnn | |
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 | |
Defined in GHC.Parser.Annotation | |
Eq AddEpAnn | |
data EpaCommentTok #
Constructors
EpaDocComment HsDocString | a docstring that can be pretty printed using pprHsDocString |
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
Data EpaCommentTok | |
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 | |
Defined in GHC.Parser.Annotation Methods showsPrec :: Int -> EpaCommentTok -> ShowS # show :: EpaCommentTok -> String # showList :: [EpaCommentTok] -> ShowS # | |
Eq EpaCommentTok | |
Defined in GHC.Parser.Annotation Methods (==) :: EpaCommentTok -> EpaCommentTok -> Bool # (/=) :: EpaCommentTok -> EpaCommentTok -> Bool # |
data EpaComment #
Constructors
EpaComment | |
Fields
|
Instances
Data EpaComment | |
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 | |
Defined in GHC.Parser.Annotation Methods showsPrec :: Int -> EpaComment -> ShowS # show :: EpaComment -> String # showList :: [EpaComment] -> ShowS # | |
Outputable EpaComment | |
Defined in GHC.Parser.Annotation Methods ppr :: EpaComment -> SDoc # | |
Eq EpaComment | |
Defined in GHC.Parser.Annotation | |
Outputable (GenLocated Anchor EpaComment) | |
Defined in GHC.Parser.Annotation Methods ppr :: GenLocated Anchor EpaComment -> SDoc # |
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.
Instances
Data HasE | |
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 # 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 | |
Eq HasE | |
Ord HasE | |
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
Constructors
UnicodeSyntax | |
NormalSyntax |
Instances
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 |
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].
Instances
IsPass 'Parsed | |
Defined in GHC.Hs.Extension | |
IsPass 'Renamed | |
Defined in GHC.Hs.Extension | |
IsPass 'Typechecked | |
Defined in GHC.Hs.Extension Methods ghcPass :: GhcPass 'Typechecked # |
type GhcTc = GhcPass 'Typechecked #
Constructors
Parsed | |
Renamed | |
Typechecked |
Instances
Data Pass | |
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 # 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 # |
data GhcPass (c :: Pass) where #
Used as a data type index for the hsSyn AST; also serves as a singleton type for Pass
Instances
type IsSrcSpanAnn (p :: Pass) a = (Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a), IsPass p) #
data ExtractedTHDocs #
Maps of docs that were added via Template Haskell's putDoc
.
Constructors
ExtractedTHDocs | |
Fields
|
Constructors
Docs | |
Fields
|
type DocStructure = [DocStructureItem] #
data DocStructureItem #
A simplified version of IE
.
Constructors
DsiSectionHeading !Int !(HsDoc GhcRn) | |
DsiDocChunk !(HsDoc GhcRn) | |
DsiNamedChunkRef !String | |
DsiExports !Avails | |
DsiModExport | |
Fields
|
Instances
NFData DocStructureItem | |
Defined in GHC.Hs.Doc Methods rnf :: DocStructureItem -> () # | |
Binary DocStructureItem | |
Defined in GHC.Hs.Doc Methods put_ :: BinHandle -> DocStructureItem -> IO () # put :: BinHandle -> DocStructureItem -> IO (Bin DocStructureItem) # get :: BinHandle -> IO DocStructureItem # | |
Outputable DocStructureItem | |
Defined in GHC.Hs.Doc Methods ppr :: DocStructureItem -> SDoc # |
data WithHsDocIdentifiers a pass #
Annotate a value with the probable identifiers found in it These will be used by haddock to generate links.
The identifiers are bundled along with their location in the source file. This is useful for tooling to know exactly where they originate.
This type is currently used in two places - for regular documentation comments,
with a
set to HsDocString
, and for adding identifier information to
warnings, where a
is StringLiteral
Constructors
WithHsDocIdentifiers | |
Fields
|
Instances
(Data pass, Data (IdP pass), Data a) => Data (WithHsDocIdentifiers a pass) | |
Defined in GHC.Hs.Doc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithHsDocIdentifiers a pass -> c (WithHsDocIdentifiers a pass) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WithHsDocIdentifiers a pass) # toConstr :: WithHsDocIdentifiers a pass -> Constr # dataTypeOf :: WithHsDocIdentifiers a pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WithHsDocIdentifiers a pass)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WithHsDocIdentifiers a pass)) # gmapT :: (forall b. Data b => b -> b) -> WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithHsDocIdentifiers a pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithHsDocIdentifiers a pass -> r # gmapQ :: (forall d. Data d => d -> u) -> WithHsDocIdentifiers a pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WithHsDocIdentifiers a pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) # | |
(NFData (IdP pass), NFData a) => NFData (WithHsDocIdentifiers a pass) | |
Defined in GHC.Hs.Doc Methods rnf :: WithHsDocIdentifiers a pass -> () # | |
Binary a => Binary (WithHsDocIdentifiers a GhcRn) | |
Defined in GHC.Hs.Doc | |
Outputable a => Outputable (WithHsDocIdentifiers a pass) | For compatibility with the existing @-ddump-parsed' output, we only show the docstring. Use |
Defined in GHC.Hs.Doc Methods ppr :: WithHsDocIdentifiers a pass -> SDoc # | |
ExactPrint a => ExactPrint (WithHsDocIdentifiers a GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: WithHsDocIdentifiers a GhcPs -> Entry # setAnnotationAnchor :: WithHsDocIdentifiers a GhcPs -> Anchor -> EpAnnComments -> WithHsDocIdentifiers a GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => WithHsDocIdentifiers a GhcPs -> EP w m (WithHsDocIdentifiers a GhcPs) # | |
(Eq (IdP pass), Eq a) => Eq (WithHsDocIdentifiers a pass) | |
Defined in GHC.Hs.Doc Methods (==) :: WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass -> Bool # (/=) :: WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass -> Bool # |
type HsDoc = WithHsDocIdentifiers HsDocString #
A docstring with the (probable) identifiers found in it.
type LIEWrappedName p = XRec p (IEWrappedName p) #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern
data IEWrappedName p #
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 (XIEName p) (LIdP p) | no extra |
IEPattern (XIEPattern p) (LIdP p) | pattern X |
IEType (XIEType p) (LIdP p) | type (:+:) |
XIEWrappedName !(XXIEWrappedName p) |
Instances
ExactPrint (IEWrappedName GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: IEWrappedName GhcPs -> Entry # setAnnotationAnchor :: IEWrappedName GhcPs -> Anchor -> EpAnnComments -> IEWrappedName GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IEWrappedName GhcPs -> EP w m (IEWrappedName GhcPs) # | |
type Anno (IEWrappedName (GhcPass _1)) | |
Defined in GHC.Hs.ImpExp |
data IEWildcard #
Wildcard in an import or export sublist, like the ..
in
import Mod ( T(Mk1, Mk2, ..) )
.
Constructors
NoIEWildcard | no wildcard in this list |
IEWildcard Int | wildcard after the given # of items in this list
The |
Instances
Data IEWildcard | |
Defined in Language.Haskell.Syntax.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 | |
Defined in Language.Haskell.Syntax.ImpExp |
data ImportListInterpretation #
Whether the import list is exactly what to import, or whether hiding
was
used, and therefore everything but what was listed should be imported
Constructors
Exactly | |
EverythingBut |
Instances
data ImportDecl pass #
Import Declaration
A single Haskell import
declaration.
Constructors
ImportDecl | |
Fields
| |
XImportDecl !(XXImportDecl pass) |
Instances
ExactPrint (ImportDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ImportDecl GhcPs -> Entry # setAnnotationAnchor :: ImportDecl GhcPs -> Anchor -> EpAnnComments -> ImportDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ImportDecl GhcPs -> EP w m (ImportDecl GhcPs) # | |
type Anno (ImportDecl (GhcPass p)) | |
Defined in GHC.Hs.ImpExp |
data ImportDeclQualifiedStyle #
If/how an import is qualified
.
Constructors
QualifiedPre |
|
QualifiedPost |
|
NotQualified | Not qualified. |
Instances
type LImportDecl pass #
Arguments
= XRec pass (ImportDecl pass) | When in a list this may have |
Located Import Declaration
data EpAnnImportDecl #
Constructors
EpAnnImportDecl | |
Instances
Data EpAnnImportDecl | |
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 # |
data XImportDeclPass #
Constructors
XImportDeclPass | |
Fields
|
Instances
Data XImportDeclPass | |
Defined in GHC.Hs.ImpExp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XImportDeclPass -> c XImportDeclPass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XImportDeclPass # toConstr :: XImportDeclPass -> Constr # dataTypeOf :: XImportDeclPass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XImportDeclPass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XImportDeclPass) # gmapT :: (forall b. Data b => b -> b) -> XImportDeclPass -> XImportDeclPass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r # gmapQ :: (forall d. Data d => d -> u) -> XImportDeclPass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> XImportDeclPass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # |
data OverLitVal #
Overloaded Literal Value
Constructors
HsIntegral !IntegralLit | Integer-looking literals; |
HsFractional !FractionalLit | Frac-looking literals |
HsIsString !SourceText !FastString | String-looking literals |
Instances
Data OverLitVal | |
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 # | |
Eq OverLitVal | |
Defined in Language.Haskell.Syntax.Lit | |
Ord OverLitVal | |
Defined in Language.Haskell.Syntax.Lit Methods compare :: OverLitVal -> OverLitVal -> Ordering # (<) :: OverLitVal -> OverLitVal -> Bool # (<=) :: OverLitVal -> OverLitVal -> Bool # (>) :: OverLitVal -> OverLitVal -> Bool # (>=) :: OverLitVal -> OverLitVal -> Bool # max :: OverLitVal -> OverLitVal -> OverLitVal # min :: OverLitVal -> OverLitVal -> OverLitVal # |
Haskell Overloaded Literal
Instances
ExactPrint (HsOverLit GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
Eq (XXOverLit p) => Eq (HsOverLit p) | |
Ord (XXOverLit p) => Ord (HsOverLit p) | |
Defined in Language.Haskell.Syntax.Lit | |
type Anno (HsOverLit (GhcPass p)) | |
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 |
HsWordPrim (XHsWordPrim x) Integer | literal |
HsInt64Prim (XHsInt64Prim x) Integer | literal |
HsWord64Prim (XHsWord64Prim x) Integer | literal |
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) |
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 Bool | Strict but not unpacked field True = we could have unpacked, but opted not to because of -O0. See Note [Detecting useless UNPACK pragmas] |
HsUnpack (Maybe Coercion) | Strict and unpacked field co :: arg-ty ~ product-ty HsBang |
Instances
Data HsImplBang | |
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 | |
Defined in GHC.Core.DataCon Methods ppr :: HsImplBang -> SDoc # |
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)
Constructors
HsSrcBang SourceText SrcUnpackedness SrcStrictness |
Instances
Data HsSrcBang | |
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 | |
Defined in GHC.Core.DataCon |
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. See Note [Located RdrNames] in GHC.Hs.Expr.
Constructors
Unambiguous (XUnambiguous pass) (XRec pass RdrName) | |
Ambiguous (XAmbiguous pass) (XRec pass RdrName) | |
XAmbiguousFieldOcc !(XXAmbiguousFieldOcc pass) |
Instances
type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass) #
Located Ambiguous Field Occurence
Field Occurrence
Represents an *occurrence* of a 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 we use the extension field to store the selector
function.
Constructors
FieldOcc | |
Fields
| |
XFieldOcc !(XXFieldOcc pass) |
Instances
ExactPrint (FieldOcc GhcPs) | |
(Eq (XRec pass RdrName), Eq (XCFieldOcc pass), Eq (XXFieldOcc pass)) => Eq (FieldOcc pass) | |
ExactPrint body => ExactPrint (HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body -> Entry # setAnnotationAnchor :: HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body -> Anchor -> EpAnnComments -> HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body -> EP w m (HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body) # | |
type Anno (FieldOcc (GhcPass p)) | |
type LHsTypeArg p = HsArg (LHsType p) (LHsKind p) #
Arguments in an expression/type after splitting
Instances
(ExactPrint tm, ExactPrint ty, Outputable tm, Outputable ty) => ExactPrint (HsArg tm ty) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint |
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 (seeHsConPatDetails
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).
Instances
(Data tyarg, Data rec, Data arg) => Data (HsConDetails tyarg arg rec) | |
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) # |
data ConDeclField pass #
Constructor Declaration Field
Constructors
ConDeclField | |
Fields
| |
XConDeclField !(XXConDeclField pass) |
Instances
ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: LocatedL [LocatedA (ConDeclField GhcPs)] -> Entry # setAnnotationAnchor :: LocatedL [LocatedA (ConDeclField GhcPs)] -> Anchor -> EpAnnComments -> LocatedL [LocatedA (ConDeclField GhcPs)] # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedL [LocatedA (ConDeclField GhcPs)] -> EP w m (LocatedL [LocatedA (ConDeclField GhcPs)]) # | |
ExactPrint (ConDeclField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ConDeclField GhcPs -> Entry # setAnnotationAnchor :: ConDeclField GhcPs -> Anchor -> EpAnnComments -> ConDeclField GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ConDeclField GhcPs -> EP w m (ConDeclField GhcPs) # | |
type Anno (ConDeclField (GhcPass p)) | |
Defined in GHC.Hs.Type | |
type Anno [LocatedA (ConDeclField (GhcPass _1))] | |
Defined in GHC.Hs.Decls |
type LConDeclField pass #
Arguments
= XRec pass (ConDeclField pass) | May have |
Located Constructor Declaration Field
data HsTupleSort #
Haskell Tuple Sort
Constructors
HsUnboxedTuple | |
HsBoxedOrConstraintTuple |
Instances
Data HsTupleSort | |
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 # |
This is used in the syntax. In constructor declaration. It must keep the arrow representation.
Instances
ExactPrint a => ExactPrint (HsScaled GhcPs a) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint |
data HsLinearArrowTokens pass #
Constructors
HsPct1 !(LHsToken "%1" pass) !(LHsUniToken "->" "\8594" pass) | |
HsLolly !(LHsToken "\8888" pass) |
Denotes the type of arrows in the surface language
Constructors
HsUnrestrictedArrow !(LHsUniToken "->" "\8594" pass) | a -> b or a → b |
HsLinearArrow !(HsLinearArrowTokens pass) | a %1 -> b or a %1 → b, or a ⊸ b |
HsExplicitMult !(LHsToken "%" pass) !(LHsType pass) !(LHsUniToken "->" "\8594" 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
|
Haskell Type Literal
Haskell Type
Constructors
Instances
DisambTD (HsType GhcPs) | |
Defined in GHC.Parser.PostProcess Methods mkHsAppTyHeadPV :: LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) # mkHsAppTyPV :: LocatedA (HsType GhcPs) -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) # mkHsAppKindTyPV :: LocatedA (HsType GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) # mkHsOpTyPV :: PromotionFlag -> LHsType GhcPs -> LocatedN RdrName -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) # mkUnpackednessPV :: Located UnpackednessPragma -> LocatedA (HsType GhcPs) -> PV (LocatedA (HsType GhcPs)) # | |
ExactPrint (HsType GhcPs) | |
type Anno (BangType (GhcPass p)) | |
Defined in GHC.Hs.Type | |
type Anno (HsKind (GhcPass p)) | |
Defined in GHC.Hs.Type | |
type Anno (HsType (GhcPass p)) | |
Defined in GHC.Hs.Type | |
type Anno [LocatedA (HsType (GhcPass p))] | |
Defined in GHC.Hs.Type | |
type Anno (FamEqn p (LocatedA (HsType p))) | |
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
ExactPrintTVFlag flag => ExactPrint (HsTyVarBndr flag GhcPs) | |
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)) | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcPs) | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcRn) | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcTc) | |
Defined in GHC.Hs.Type |
These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.
Constructors
HsIPName FastString |
Instances
Data HsIPName | |
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 # | |
ExactPrint HsIPName | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
Eq HsIPName | |
type Anno HsIPName | |
Defined in GHC.Hs.Type |
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 | |
XHsSigType !(XXHsSigType pass) |
Instances
ExactPrint (HsSigType GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
type Anno (HsSigType (GhcPass p)) | |
Defined in GHC.Hs.Type |
type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) #
Located Haskell Signature Wildcard Type
type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) #
Located Haskell Wildcard Type
type LHsSigType pass = XRec pass (HsSigType pass) #
Located Haskell Signature Type
data HsPatSigType pass #
Types that can appear in pattern signatures, as well as the signatures for
term-level binders in RULES.
See Note [Pattern signature binders and scoping]
.
This is very similar to HsSigWcType
, but with
slightly different semantics: see Note [HsType binders]
.
See also Note [The wildcard story for types]
.
Constructors
HsPS | |
XHsPatSigType !(XXHsPatSigType pass) |
Instances
ExactPrint (HsPatSigType GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsPatSigType GhcPs -> Entry # setAnnotationAnchor :: HsPatSigType GhcPs -> Anchor -> EpAnnComments -> HsPatSigType GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsPatSigType GhcPs -> EP w m (HsPatSigType GhcPs) # |
data HsWildCardBndrs pass thing #
Haskell Wildcard Binders
Constructors
HsWC | |
XHsWildCardBndrs !(XXHsWildCardBndrs pass thing) |
Instances
ExactPrint body => ExactPrint (HsWildCardBndrs GhcPs body) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsWildCardBndrs GhcPs body -> Entry # setAnnotationAnchor :: HsWildCardBndrs GhcPs body -> Anchor -> EpAnnComments -> HsWildCardBndrs GhcPs body # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsWildCardBndrs GhcPs body -> EP w m (HsWildCardBndrs GhcPs body) # |
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 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.
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.,
|
Fields
| |
HsOuterExplicit | Explicit forall, e.g.,
|
Fields
| |
XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass) |
Instances
ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsOuterTyVarBndrs flag GhcPs -> Entry # setAnnotationAnchor :: HsOuterTyVarBndrs flag GhcPs -> Anchor -> EpAnnComments -> HsOuterTyVarBndrs flag GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsOuterTyVarBndrs flag GhcPs -> EP w m (HsOuterTyVarBndrs flag GhcPs) # | |
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) | |
Defined in GHC.Hs.Type |
data LHsQTyVars pass #
Located Haskell Quantified Type Variables
Constructors
HsQTvs | |
Fields
| |
XLHsQTyVars !(XXLHsQTyVars pass) |
type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass) #
Located Haskell Type Variable Binder
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 |
Fields
| |
HsForAllInvis | An invisible |
Fields
| |
XHsForAllTelescope !(XXHsForAllTelescope pass) |
Instances
ExactPrint (HsForAllTelescope GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsForAllTelescope GhcPs -> Entry # setAnnotationAnchor :: HsForAllTelescope GhcPs -> Anchor -> EpAnnComments -> HsForAllTelescope GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsForAllTelescope GhcPs -> EP w m (HsForAllTelescope GhcPs) # |
Arguments
= XRec pass (HsType pass) | May have |
Located Haskell Type
type LHsContext pass #
Arguments
= XRec pass (HsContext pass) |
|
Located Haskell Context
data HsFieldBind lhs rhs #
Haskell Field Binding
For details on above see Note [exact print annotations] in GHC.Parser.Annotation
Constructors
HsFieldBind | |
Instances
type HsRecUpdField p = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr p) #
Haskell Record Update Field
type HsRecField p arg = HsFieldBind (LFieldOcc p) arg #
Haskell Record Field
type LHsRecUpdField p = XRec p (HsRecUpdField p) #
Located Haskell Record Update Field
type LHsRecField p arg = XRec p (HsRecField p arg) #
Located Haskell Record Field
type LHsFieldBind p id arg = XRec p (HsFieldBind id arg) #
Located Haskell Record Field
newtype RecFieldsDotDot #
Newtype to be able to have a specific XRec instance for the Int in rec_dotdot
Constructors
RecFieldsDotDot | |
Fields |
Instances
data HsRecFields p arg #
Haskell Record Fields
HsRecFields is used only for patterns and expressions (not data type declarations)
Constructors
HsRecFields | |
Fields
|
Instances
ExactPrint body => ExactPrint (HsRecFields GhcPs body) | |
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) # |
type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) (LPat p) (HsRecFields p (LPat p)) #
Haskell Constructor Pattern Details
data HsConPatTyArg p #
Type argument in a data constructor pattern,
e.g. the @a
in f (Just @a x) = ...
.
Constructors
HsConPatTyArg !(LHsToken "@" p) (HsPatSigType p) |
Instances
ExactPrint (HsConPatTyArg GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsConPatTyArg GhcPs -> Entry # setAnnotationAnchor :: HsConPatTyArg GhcPs -> Anchor -> EpAnnComments -> HsConPatTyArg GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsConPatTyArg GhcPs -> EP w m (HsConPatTyArg GhcPs) # |
data HsPatSynDir id #
Haskell Pattern Synonym Direction
Constructors
Unidirectional | |
ImplicitBidirectional | |
ExplicitBidirectional (MatchGroup id (LHsExpr id)) |
data RecordPatSynField pass #
Record Pattern Synonym Field
Constructors
RecordPatSynField | |
Fields
|
Instances
ExactPrint (RecordPatSynField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: RecordPatSynField GhcPs -> Entry # setAnnotationAnchor :: RecordPatSynField GhcPs -> Anchor -> EpAnnComments -> RecordPatSynField GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => RecordPatSynField GhcPs -> EP w m (RecordPatSynField GhcPs) # |
type HsPatSynDetails pass = HsConDetails Void (LIdP pass) [RecordPatSynField pass] #
Haskell Pattern Synonym Details
Fixity Signature
Constructors
FixitySig (XFixitySig pass) [LIdP pass] Fixity | |
XFixitySig !(XXFixitySig pass) |
Instances
type Anno (FixitySig (GhcPass p)) | |
Defined in GHC.Hs.Binds |
type LFixitySig pass = XRec pass (FixitySig pass) #
Located Fixity Signature
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
|
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 |
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) (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) (LBooleanFormula (LIdP pass)) | A minimal complete definition pragma {-# MINIMAL a | (b, c | (d | e)) #-} |
SCCFunSig (XSCCFunSig pass) (LIdP pass) (Maybe (XRec pass StringLiteral)) | A "set cost centre" pragma for declarations {-# SCC funName #-} or {-# SCC funName "cost_centre_name" #-} |
CompleteMatchSig (XCompleteMatchSig pass) (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
ExactPrint (Sig GhcPs) | |
type Anno (Sig (GhcPass p)) | |
Defined in GHC.Hs.Binds |
Implicit parameter bindings.
Instances
ExactPrint (IPBind GhcPs) | |
type Anno (IPBind (GhcPass p)) | |
Defined in GHC.Hs.Binds |
type LIPBind id = XRec id (IPBind id) #
Located Implicit Parameter Binding
May have AnnKeywordId
: AnnSemi
when in a
list
Haskell Implicit Parameter Bindings
Constructors
IPBinds (XIPBinds id) [LIPBind id] | |
XHsIPBinds !(XXHsIPBinds id) |
Instances
data PatSynBind idL idR #
AnnKeywordId
:AnnPattern
,AnnEqual
,AnnLarrow
,AnnWhere
,AnnOpen
'{'
,AnnClose
'}'
,
Pattern Synonym binding
Constructors
PSB | |
Fields
| |
XPatSynBind !(XXPatSynBind idL idR) |
Instances
ExactPrint (PatSynBind GhcPs GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: PatSynBind GhcPs GhcPs -> Entry # setAnnotationAnchor :: PatSynBind GhcPs GhcPs -> Anchor -> EpAnnComments -> PatSynBind GhcPs GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => PatSynBind GhcPs GhcPs -> EP w m (PatSynBind GhcPs GhcPs) # |
Haskell Binding with separate Left and Right id's
Constructors
FunBind | Function-like Binding FunBind is used for both functions Reason 1: Special case for type inference: see 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 Strict bindings have their strictness recorded in the |
Fields
| |
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. |
VarBind | Variable Binding Dictionary binding and suchlike. All VarBinds are introduced by the type checker |
PatSynBind | Patterns Synonym Binding |
Fields
| |
XHsBindsLR !(XXHsBindsLR idL idR) |
Instances
ExactPrint (HsBind GhcPs) | |
type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) | |
Defined in GHC.Hs.Binds |
type LHsBindLR idL idR = XRec idL (HsBindLR idL idR) #
Located Haskell Binding with separate Left and Right identifier types
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
data HsValBindsLR idL idR #
Haskell Value bindings with separate Left and Right identifier types (not implicit parameters) Used for both top level and nested bindings May contain pattern synonym bindings
Constructors
ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR] | Value Bindings In Before renaming RHS; idR is always RdrName Not dependency analysed Recursive by default |
XValBindsLR !(XXValBindsLR idL idR) | Value Bindings Out After renaming RHS; idR can be Name or Id Dependency analysed, later bindings in the list may depend on earlier ones. |
Instances
ExactPrint (HsValBindsLR GhcPs GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsValBindsLR GhcPs GhcPs -> Entry # setAnnotationAnchor :: HsValBindsLR GhcPs GhcPs -> Anchor -> EpAnnComments -> HsValBindsLR GhcPs GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsValBindsLR GhcPs GhcPs -> EP w m (HsValBindsLR GhcPs GhcPs) # |
type HsValBinds id = HsValBindsLR id id #
Haskell Value Bindings
type LHsLocalBindsLR idL idR = XRec idL (HsLocalBindsLR idL idR) #
data HsLocalBindsLR idL idR #
Haskell Local Bindings with separate Left and Right identifier types
Bindings in a 'let' expression or a 'where' clause
Constructors
HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR) | Haskell Value Bindings |
HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR) | Haskell Implicit Parameter Bindings |
EmptyLocalBinds (XEmptyLocalBinds idL idR) | Empty Local Bindings |
XHsLocalBindsLR !(XXHsLocalBindsLR idL idR) |
Instances
ExactPrint (HsLocalBinds GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsLocalBinds GhcPs -> Entry # setAnnotationAnchor :: HsLocalBinds GhcPs -> Anchor -> EpAnnComments -> HsLocalBinds GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsLocalBinds GhcPs -> EP w m (HsLocalBinds GhcPs) # |
type LHsLocalBinds id = XRec id (HsLocalBinds id) #
Located Haskell local bindings
type HsLocalBinds id = HsLocalBindsLR id id #
Haskell Local Bindings
data RoleAnnotDecl pass #
Role Annotation Declaration
Constructors
RoleAnnotDecl (XCRoleAnnotDecl pass) (LIdP pass) [XRec pass (Maybe Role)] | |
XRoleAnnotDecl !(XXRoleAnnotDecl pass) |
Instances
ExactPrint (RoleAnnotDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: RoleAnnotDecl GhcPs -> Entry # setAnnotationAnchor :: RoleAnnotDecl GhcPs -> Anchor -> EpAnnComments -> RoleAnnotDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => RoleAnnotDecl GhcPs -> EP w m (RoleAnnotDecl GhcPs) # | |
type Anno (RoleAnnotDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LRoleAnnotDecl pass = XRec pass (RoleAnnotDecl pass) #
Located Role Annotation Declaration
data AnnProvenance pass #
Annotation Provenance
Constructors
ValueAnnProvenance (LIdP pass) | |
TypeAnnProvenance (LIdP pass) | |
ModuleAnnProvenance |
Warning pragma Declaration
Constructors
Warning (XWarning pass) [LIdP pass] (WarningTxt pass) | |
XWarnDecl !(XXWarnDecl pass) |
Instances
ExactPrint (WarnDecl GhcPs) | |
type Anno (WarnDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Warning pragma Declarations
Constructors
Warnings | |
Fields
| |
XWarnDecls !(XXWarnDecls pass) |
Instances
ExactPrint (WarnDecls GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
type Anno (WarnDecls (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LWarnDecls pass = XRec pass (WarnDecls pass) #
Located Warning Declarations
Documentation comment Declaration
Constructors
DocCommentNext (LHsDoc pass) | |
DocCommentPrev (LHsDoc pass) | |
DocCommentNamed String (LHsDoc pass) | |
DocGroup Int (LHsDoc pass) |
Instances
(Data pass, Data (IdP pass)) => Data (DocDecl pass) | |
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 pass -> c (DocDecl pass) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DocDecl pass) # toConstr :: DocDecl pass -> Constr # dataTypeOf :: DocDecl pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DocDecl pass)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DocDecl pass)) # gmapT :: (forall b. Data b => b -> b) -> DocDecl pass -> DocDecl pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl pass -> r # gmapQ :: (forall d. Data d => d -> u) -> DocDecl pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DocDecl pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DocDecl pass -> m (DocDecl pass) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl pass -> m (DocDecl pass) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl pass -> m (DocDecl pass) # | |
ExactPrint (DocDecl GhcPs) | |
type Anno (DocDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Rule Declaration
Constructors
HsRule | |
Fields
| |
XRuleDecl !(XXRuleDecl pass) |
Instances
ExactPrint (RuleDecl GhcPs) | |
type Anno (RuleDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Rule Declarations
Constructors
HsRules | |
Fields
| |
XRuleDecls !(XXRuleDecls pass) |
Instances
ExactPrint (RuleDecls GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
type Anno (RuleDecls (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LRuleDecls pass = XRec pass (RuleDecls pass) #
Located Rule Declarations
data ForeignExport pass #
Constructors
CExport (XCExport pass) (XRec pass CExportSpec) | |
XForeignExport !(XXForeignExport pass) |
Instances
ExactPrint (ForeignExport GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ForeignExport GhcPs -> Entry # setAnnotationAnchor :: ForeignExport GhcPs -> Anchor -> EpAnnComments -> ForeignExport GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ForeignExport GhcPs -> EP w m (ForeignExport GhcPs) # |
data CImportSpec #
Constructors
CLabel CLabelString | |
CFunction CCallTarget | |
CWrapper |
Instances
Data CImportSpec | |
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 ForeignImport pass #
Constructors
CImport (XCImport pass) (XRec pass CCallConv) (XRec pass Safety) (Maybe Header) CImportSpec | |
XForeignImport !(XXForeignImport pass) |
Instances
ExactPrint (ForeignImport GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ForeignImport GhcPs -> Entry # setAnnotationAnchor :: ForeignImport GhcPs -> Anchor -> EpAnnComments -> ForeignImport GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ForeignImport GhcPs -> EP w m (ForeignImport GhcPs) # |
data ForeignDecl pass #
Foreign Declaration
Constructors
ForeignImport | |
Fields
| |
ForeignExport | |
Fields
| |
XForeignDecl !(XXForeignDecl pass) |
Instances
ExactPrint (ForeignDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ForeignDecl GhcPs -> Entry # setAnnotationAnchor :: ForeignDecl GhcPs -> Anchor -> EpAnnComments -> ForeignDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ForeignDecl GhcPs -> EP w m (ForeignDecl GhcPs) # | |
type Anno (ForeignDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LForeignDecl pass = XRec pass (ForeignDecl pass) #
Located Foreign Declaration
data DefaultDecl pass #
Default Declaration
Constructors
DefaultDecl (XCDefaultDecl pass) [LHsType pass] | |
XDefaultDecl !(XXDefaultDecl pass) |
Instances
ExactPrint (DefaultDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: DefaultDecl GhcPs -> Entry # setAnnotationAnchor :: DefaultDecl GhcPs -> Anchor -> EpAnnComments -> DefaultDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DefaultDecl GhcPs -> EP w m (DefaultDecl GhcPs) # | |
type Anno (DefaultDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LDefaultDecl pass = XRec pass (DefaultDecl pass) #
Located Default Declaration
type LDerivStrategy pass = XRec pass (DerivStrategy pass) #
A Located
DerivStrategy
.
Stand-alone 'deriving instance' declaration
Constructors
DerivDecl | |
Fields
| |
XDerivDecl !(XXDerivDecl pass) |
Instances
ExactPrint (DerivDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
type Anno (DerivDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LDerivDecl pass = XRec pass (DerivDecl pass) #
Located stand-alone 'deriving instance' declaration
Instance Declaration
Constructors
ClsInstD | |
Fields
| |
DataFamInstD | |
Fields
| |
TyFamInstD | |
Fields
| |
XInstDecl !(XXInstDecl pass) |
Instances
ExactPrint (InstDecl GhcPs) | |
type Anno (InstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
data ClsInstDecl pass #
Class Instance Declaration
- AnnKeywordId
: AnnInstance
,
AnnWhere
,
AnnOpen
,AnnClose
,
For details on above see Note [exact print annotations] in GHC.Parser.Annotation
Constructors
ClsInstDecl | |
Fields
| |
XClsInstDecl !(XXClsInstDecl pass) |
Instances
ExactPrint (ClsInstDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ClsInstDecl GhcPs -> Entry # setAnnotationAnchor :: ClsInstDecl GhcPs -> Anchor -> EpAnnComments -> ClsInstDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ClsInstDecl GhcPs -> EP w m (ClsInstDecl GhcPs) # | |
type Anno (ClsInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LClsInstDecl pass = XRec pass (ClsInstDecl pass) #
Located Class Instance Declaration
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
ExactPrint body => ExactPrint (FamEqn GhcPs body) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint | |
type Anno (FamEqn (GhcPass p) _1) | |
Defined in GHC.Hs.Decls | |
type Anno (FamEqn (GhcPass p) _1) | |
Defined in GHC.Hs.Decls | |
type Anno (FamEqn p (LocatedA (HsType p))) | |
Defined in GHC.Hs.Decls |
newtype DataFamInstDecl pass #
Data Family Instance Declaration
Constructors
DataFamInstDecl | |
Fields
|
Instances
type Anno (DataFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LDataFamInstDecl pass = XRec pass (DataFamInstDecl pass) #
Located Data Family Instance Declaration
data TyFamInstDecl pass #
Type Family Instance Declaration
Constructors
TyFamInstDecl | |
Fields
| |
XTyFamInstDecl !(XXTyFamInstDecl pass) |
Instances
ExactPrint (TyFamInstDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: TyFamInstDecl GhcPs -> Entry # setAnnotationAnchor :: TyFamInstDecl GhcPs -> Anchor -> EpAnnComments -> TyFamInstDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => TyFamInstDecl GhcPs -> EP w m (TyFamInstDecl GhcPs) # | |
type Anno (TyFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
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 TyFamDefltDecl = TyFamInstDecl #
Type family default declarations.
A convenient synonym for TyFamInstDecl
.
See Note [Type family instance declarations in HsSyn]
.
type TyFamInstEqn pass = FamEqn pass (LHsType pass) #
Type Family Instance Equation
type HsTyPats pass = [LHsTypeArg pass] #
Haskell Type Patterns
type LTyFamInstEqn pass #
Arguments
= XRec pass (TyFamInstEqn pass) | May have |
Located Type Family Instance Equation
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]) (LHsUniToken "->" "\8594" pass) |
type HsConDeclH98Details pass = HsConDetails Void (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass]) #
The arguments in a Haskell98-style data constructor.
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 = IntMkT
Int | MkT2 data T a where IntMkT
Int :: T Int
AnnKeywordId
s :AnnOpen
,AnnDotdot
,AnnCLose
,AnnEqual
,AnnVbar
,AnnDarrow
,AnnDarrow
,AnnForall
,AnnDot
data Constructor Declaration
Constructors
ConDeclGADT | |
Fields
| |
ConDeclH98 | |
Fields
| |
XConDecl !(XXConDecl pass) |
Instances
ExactPrint (ConDecl GhcPs) | |
type Anno (ConDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
Arguments
= XRec pass (ConDecl pass) | May have |
Located data Constructor Declaration
data DataDefnCons a #
Whether a data-type declaration is data
or newtype
, and its constructors.
Constructors
NewTypeCon a | |
DataTypeCons Bool [a] |
Instances
Foldable DataDefnCons | |
Defined in Language.Haskell.Syntax.Decls Methods fold :: Monoid m => DataDefnCons m -> m # foldMap :: Monoid m => (a -> m) -> DataDefnCons a -> m # foldMap' :: Monoid m => (a -> m) -> DataDefnCons a -> m # foldr :: (a -> b -> b) -> b -> DataDefnCons a -> b # foldr' :: (a -> b -> b) -> b -> DataDefnCons a -> b # foldl :: (b -> a -> b) -> b -> DataDefnCons a -> b # foldl' :: (b -> a -> b) -> b -> DataDefnCons a -> b # foldr1 :: (a -> a -> a) -> DataDefnCons a -> a # foldl1 :: (a -> a -> a) -> DataDefnCons a -> a # toList :: DataDefnCons a -> [a] # null :: DataDefnCons a -> Bool # length :: DataDefnCons a -> Int # elem :: Eq a => a -> DataDefnCons a -> Bool # maximum :: Ord a => DataDefnCons a -> a # minimum :: Ord a => DataDefnCons a -> a # sum :: Num a => DataDefnCons a -> a # product :: Num a => DataDefnCons a -> a # | |
Traversable DataDefnCons | |
Defined in Language.Haskell.Syntax.Decls Methods traverse :: Applicative f => (a -> f b) -> DataDefnCons a -> f (DataDefnCons b) # sequenceA :: Applicative f => DataDefnCons (f a) -> f (DataDefnCons a) # mapM :: Monad m => (a -> m b) -> DataDefnCons a -> m (DataDefnCons b) # sequence :: Monad m => DataDefnCons (m a) -> m (DataDefnCons a) # | |
Functor DataDefnCons | |
Defined in Language.Haskell.Syntax.Decls Methods fmap :: (a -> b) -> DataDefnCons a -> DataDefnCons b # (<$) :: a -> DataDefnCons b -> DataDefnCons a # | |
Data a => Data (DataDefnCons a) | |
Defined in Language.Haskell.Syntax.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDefnCons a -> c (DataDefnCons a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataDefnCons a) # toConstr :: DataDefnCons a -> Constr # dataTypeOf :: DataDefnCons a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataDefnCons a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataDefnCons a)) # gmapT :: (forall b. Data b => b -> b) -> DataDefnCons a -> DataDefnCons a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDefnCons a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDefnCons a -> r # gmapQ :: (forall d. Data d => d -> u) -> DataDefnCons a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDefnCons a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDefnCons a -> m (DataDefnCons a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDefnCons a -> m (DataDefnCons a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDefnCons a -> m (DataDefnCons a) # | |
Eq a => Eq (DataDefnCons a) | |
Defined in Language.Haskell.Syntax.Decls Methods (==) :: DataDefnCons a -> DataDefnCons a -> Bool # (/=) :: DataDefnCons a -> DataDefnCons a -> Bool # |
When we only care whether a data-type declaration is `data` or `newtype`, but not what constructors it has
Instances
Data NewOrData | |
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 # | |
Eq NewOrData | |
data StandaloneKindSig pass #
Constructors
StandaloneKindSig (XStandaloneKindSig pass) (LIdP pass) (LHsSigType pass) | |
XStandaloneKindSig !(XXStandaloneKindSig pass) |
Instances
ExactPrint (StandaloneKindSig GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: StandaloneKindSig GhcPs -> Entry # setAnnotationAnchor :: StandaloneKindSig GhcPs -> Anchor -> EpAnnComments -> StandaloneKindSig GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StandaloneKindSig GhcPs -> EP w m (StandaloneKindSig GhcPs) # | |
type Anno (StandaloneKindSig (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LStandaloneKindSig pass = XRec pass (StandaloneKindSig pass) #
Located Standalone Kind Signature
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 Example: |
DctMulti (XDctMulti pass) [LHsSigType pass] | A Example: |
XDerivClauseTys !(XXDerivClauseTys pass) |
Instances
ExactPrint (DerivClauseTys GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: DerivClauseTys GhcPs -> Entry # setAnnotationAnchor :: DerivClauseTys GhcPs -> Anchor -> EpAnnComments -> DerivClauseTys GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DerivClauseTys GhcPs -> EP w m (DerivClauseTys GhcPs) # | |
type Anno (DerivClauseTys (GhcPass _1)) | |
Defined in GHC.Hs.Decls |
type LDerivClauseTys pass = XRec pass (DerivClauseTys pass) #
data HsDerivingClause pass #
A single deriving
clause of a data declaration.
Constructors
HsDerivingClause | |
Fields
| |
XHsDerivingClause !(XXHsDerivingClause pass) |
Instances
ExactPrint (HsDerivingClause GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: HsDerivingClause GhcPs -> Entry # setAnnotationAnchor :: HsDerivingClause GhcPs -> Anchor -> EpAnnComments -> HsDerivingClause GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsDerivingClause GhcPs -> EP w m (HsDerivingClause GhcPs) # | |
type Anno (HsDerivingClause (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LHsDerivingClause pass = XRec pass (HsDerivingClause pass) #
type HsDeriving pass #
Arguments
= [LHsDerivingClause pass] | The optional The list of |
Haskell Deriving clause
data HsDataDefn pass #
Haskell Data type Definition
Constructors
HsDataDefn | Declares a data type or newtype, giving its constructors
|
Fields
| |
XHsDataDefn !(XXHsDataDefn pass) |
data FamilyInfo pass #
Constructors
DataFamily | |
OpenTypeFamily | |
ClosedTypeFamily (Maybe [LTyFamInstEqn pass]) |
|
type LInjectivityAnn pass = XRec pass (InjectivityAnn pass) #
Located Injectivity Annotation
data FamilyDecl pass #
type Family Declaration
Constructors
FamilyDecl | |
Fields
| |
XFamilyDecl !(XXFamilyDecl pass) |
Instances
ExactPrint (FamilyDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: FamilyDecl GhcPs -> Entry # setAnnotationAnchor :: FamilyDecl GhcPs -> Anchor -> EpAnnComments -> FamilyDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FamilyDecl GhcPs -> EP w m (FamilyDecl GhcPs) # | |
type Anno (FamilyDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LFamilyDecl pass = XRec pass (FamilyDecl pass) #
Located type Family Declaration
data FamilyResultSig pass #
type Family Result Signature
Constructors
NoSig (XNoSig pass) | |
KindSig (XCKindSig pass) (LHsKind pass) | |
TyVarSig (XTyVarSig pass) (LHsTyVarBndr () pass) | |
XFamilyResultSig !(XXFamilyResultSig pass) |
Instances
type Anno (FamilyResultSig (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LFamilyResultSig pass = XRec pass (FamilyResultSig pass) #
Located type Family Result Signature
Type or Class Group
Constructors
TyClGroup | |
Fields
| |
XTyClGroup !(XXTyClGroup pass) |
A type or class declaration.
Constructors
FamDecl | type/data family T :: *->* |
Fields
| |
SynDecl |
|
Fields
| |
DataDecl |
|
Fields
| |
ClassDecl | |
Fields
| |
XTyClDecl !(XXTyClDecl pass) |
Instances
ExactPrint (TyClDecl GhcPs) | |
type Anno (TyClDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
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 |
BareSplice | bare splice |
Instances
data SpliceDecl p #
Splice Declaration
Constructors
SpliceDecl (XSpliceDecl p) (XRec p (HsUntypedSplice p)) SpliceDecoration | |
XSpliceDecl !(XXSpliceDecl p) |
Instances
ExactPrint (SpliceDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: SpliceDecl GhcPs -> Entry # setAnnotationAnchor :: SpliceDecl GhcPs -> Anchor -> EpAnnComments -> SpliceDecl GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => SpliceDecl GhcPs -> EP w m (SpliceDecl GhcPs) # | |
type Anno (SpliceDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls |
type LSpliceDecl pass = XRec pass (SpliceDecl pass) #
Located Splice Declaration
Constructors
HsGroup | |
Fields
| |
XHsGroup !(XXHsGroup 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 p) | Documentation comment declaration |
RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p) | Role annotation declaration |
XHsDecl !(XXHsDecl p) |
Instances
ExactPrint (HsDecl GhcPs) | |
type Anno (HsDecl (GhcPass _1)) | |
Defined in GHC.Hs.Decls |
data HsDoFlavour #
Constructors
DoExpr (Maybe ModuleName) |
|
MDoExpr (Maybe ModuleName) |
|
GhciStmtCtxt | A command-line Stmt in GHCi pat <- rhs |
ListComp | |
MonadComp |
data HsArrowMatchContext #
Haskell arrow match context.
Constructors
ProcExpr | A proc expression |
ArrowCaseAlt | A case alternative inside arrow notation |
ArrowLamCaseAlt LamCaseVariant | A case or cases alternative inside arrow notation |
KappaExpr | An arrow kappa abstraction |
data HsStmtContext p #
Haskell Statement Context.
Constructors
HsDoStmt HsDoFlavour | Context for HsDo (do-notation and comprehensions) |
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 |
ArrowExpr | do-notation in an arrow-command context |
data HsMatchContext p #
Haskell Match Context
Context of a pattern match. This is more subtle than it would seem. See Note [FunBind vs PatBind].
Constructors
FunRhs | A pattern matching on an argument of a function binding |
Fields
| |
LambdaExpr | Patterns of a lambda |
CaseAlt | Patterns and guards in a case alternative |
LamCaseAlt LamCaseVariant | Patterns and guards in |
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 ArithSeqInfo id #
Arithmetic Sequence Information
Haskell (Untyped) Quote = Expr + Pat + Type + Var
data ApplicativeArg idL #
Applicative Argument
Constructors
ApplicativeArgOne | |
Fields
| |
ApplicativeArgMany | |
Fields
| |
XApplicativeArg !(XXApplicativeArg idL) |
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.
data ParStmtBlock idL idR #
Parenthesised Statement Block
Constructors
ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR) | |
XParStmtBlock !(XXParStmtBlock idL idR) |
Instances
ExactPrint (ParStmtBlock GhcPs GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: ParStmtBlock GhcPs GhcPs -> Entry # setAnnotationAnchor :: ParStmtBlock GhcPs GhcPs -> Anchor -> EpAnnComments -> ParStmtBlock GhcPs GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => ParStmtBlock GhcPs GhcPs -> EP w m (ParStmtBlock GhcPs GhcPs) # |
Instances
Data TransForm | |
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 # |
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 | |
ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR)) |
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 | |
RecStmt | |
Fields
| |
XStmtLR !(XXStmtLR idL idR body) |
Instances
type GuardLStmt id = LStmt id (LHsExpr id) #
Guard Located Statement
type LStmtLR idL idR body = XRec idL (StmtLR idL idR body) #
Located Statement with separate Left and Right id's
Guarded Right Hand Side.
Constructors
GRHS (XCGRHS p body) [GuardLStmt p] body | |
XGRHS !(XXGRHS p body) |
Instances
type LMatch id body = XRec id (Match id body) #
Located Match
May have AnnKeywordId
: AnnSemi
when in a
list
type HsRecordBinds p = HsRecFields p (LHsExpr p) #
Haskell Record Bindings
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
data HsArrAppType #
Haskell arrow application type.
Constructors
HsHigherOrderApp | First order arrow application |
HsFirstOrderApp | Higher order arrow application |
Instances
Data HsArrAppType | |
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 # |
Haskell Command (e.g. a "statement" in an Arrow proc block)
Constructors
Instances
data LamCaseVariant #
Which kind of lambda case are we dealing with?
Instances
Data LamCaseVariant | |
Defined in Language.Haskell.Syntax.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LamCaseVariant -> c LamCaseVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LamCaseVariant # toConstr :: LamCaseVariant -> Constr # dataTypeOf :: LamCaseVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LamCaseVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LamCaseVariant) # gmapT :: (forall b. Data b => b -> b) -> LamCaseVariant -> LamCaseVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LamCaseVariant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LamCaseVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> LamCaseVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LamCaseVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LamCaseVariant -> m LamCaseVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LamCaseVariant -> m LamCaseVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LamCaseVariant -> m LamCaseVariant # | |
Eq LamCaseVariant | |
Defined in Language.Haskell.Syntax.Expr Methods (==) :: LamCaseVariant -> LamCaseVariant -> Bool # (/=) :: LamCaseVariant -> LamCaseVariant -> Bool # |
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) | Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension |
Instances
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))
A pragma, written as {-# ... #-}, that may appear within an expression.
Constructors
HsPragSCC (XSCC p) StringLiteral | |
XHsPragE !(XXPragE p) |
Instances
data DotFieldOcc p #
Constructors
DotFieldOcc | |
Fields
| |
XDotFieldOcc !(XXDotFieldOcc p) |
Instances
ExactPrint (DotFieldOcc GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.ExactPrint Methods getAnnotationEntry :: DotFieldOcc GhcPs -> Entry # setAnnotationAnchor :: DotFieldOcc GhcPs -> Anchor -> EpAnnComments -> DotFieldOcc GhcPs # exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DotFieldOcc GhcPs -> EP w m (DotFieldOcc GhcPs) # | |
type Anno (DotFieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Expr |
type LHsRecUpdProj p = XRec p (RecUpdProj p) #
type RecUpdProj p = RecProj p (LHsExpr p) #
type LHsRecProj p arg = XRec p (RecProj p arg) #
type RecProj p arg = HsFieldBind (LFieldLabelStrings p) arg #
newtype FieldLabelStrings p #
Constructors
FieldLabelStrings [XRec p (DotFieldOcc p)] |
Instances
type LFieldLabelStrings p = XRec p (FieldLabelStrings p) #
RecordDotSyntax field updates
data HsUntypedSpliceResult thing #
Constructors
HsUntypedSpliceTop | |
Fields
| |
HsUntypedSpliceNested SplicePointName |
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
Data ThModFinalizers | |
Defined in GHC.Hs.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 # |
type SplicePointName = Name #
Haskell Module
All we actually declare here is the top-level structure for a module.
Constructors
HsModule | |
Fields
| |
XModule !(XXModule p) |
Instances
HasDecls ParsedSource | |
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 # | |
ExactPrint (HsModule GhcPs) | 'Located (HsModule GhcPs)' corresponds to |
class OutputableBndrFlag flag (p :: Pass) #
Minimal complete definition
pprTyVarBndr
Instances
OutputableBndrFlag Specificity p | |
Defined in GHC.Hs.Type Methods pprTyVarBndr :: HsTyVarBndr Specificity (GhcPass p) -> SDoc | |
OutputableBndrFlag () p | |
Defined in GHC.Hs.Type Methods pprTyVarBndr :: HsTyVarBndr () (GhcPass p) -> SDoc |
The extension field for HsPatSigType
, which is only used in the
renamer onwards. See Note [Pattern signature binders and scoping]
.
Constructors
HsPSRn | |
Fields
|
Instances
Data HsPSRn | |
Defined in GHC.Hs.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 # |
type EpAnnForallTy #
Constructors
OverLitTc | |
Fields
|
Constructors
OverLitRn | |
Fields
|
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
Data TcSpecPrag | |
Defined in GHC.Hs.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 # | |
Outputable TcSpecPrag | |
Defined in GHC.Hs.Binds Methods ppr :: TcSpecPrag -> SDoc # |
type LTcSpecPrag = Located TcSpecPrag #
Located Type checker Specification Pragmas
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
Data TcSpecPrags | |
Defined in GHC.Hs.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 # |
Instances
Data AnnSig | |
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 # |
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
Instances
Data IdSig | |
Defined in GHC.Hs.Binds Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IdSig -> c IdSig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IdSig # dataTypeOf :: IdSig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IdSig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IdSig) # gmapT :: (forall b. Data b => b -> b) -> IdSig -> IdSig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IdSig -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IdSig -> r # gmapQ :: (forall d. Data d => d -> u) -> IdSig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IdSig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # |
Typechecked, generalised bindings, used in the output to the type checker. See Note [AbsBinds].
Constructors
AbsBinds | |
Fields
|
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
|
data HsPatExpansion a b #
Constructors
HsPatExpanded a b |
Instances
(Data a, Data b) => Data (HsPatExpansion a b) | |
Defined in GHC.Hs.Pat Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsPatExpansion a b -> c (HsPatExpansion a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatExpansion a b) # toConstr :: HsPatExpansion a b -> Constr # dataTypeOf :: HsPatExpansion a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatExpansion a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatExpansion a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsPatExpansion a b -> HsPatExpansion a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatExpansion a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatExpansion a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) # | |
(Outputable a, Outputable b) => Outputable (HsPatExpansion a b) | |
Defined in GHC.Hs.Pat Methods ppr :: HsPatExpansion a b -> SDoc # |
data XXPatGhcTc #
Extension constructor for Pat, added after typechecking.
Constructors
CoPat | Coercion Pattern (translation only) During desugaring a (CoPat co pat) turns into a cast with |
Fields
| |
ExpansionPat (Pat GhcRn) (Pat GhcTc) | Pattern expansion: original pattern, and desugared pattern, for RebindableSyntax and other overloaded syntax such as OverloadedLists. See Note [Rebindable syntax and HsExpansion]. |
data EpAnnSumPat #
Constructors
EpAnnSumPat | |
Fields
|
Instances
Data EpAnnSumPat | |
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 # |
Constructors
HsRuleAnn | |
Fields
|
Instances
Data HsRuleAnn | |
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 | |
Instances
Data HsRuleRn | |
Defined in GHC.Hs.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 XViaStrategyPs #
Constructors
XViaStrategyPs (EpAnn [AddEpAnn]) (LHsSigType GhcPs) |
Instances
Outputable XViaStrategyPs | |
Defined in GHC.Hs.Decls Methods ppr :: XViaStrategyPs -> SDoc # |
data DataDeclRn #
Constructors
DataDeclRn | |
Fields
|
Instances
Data DataDeclRn | |
Defined in GHC.Hs.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 PendingTcSplice #
Pending Type-checker Splice
Constructors
PendingTcSplice SplicePointName (LHsExpr GhcTc) |
Instances
Outputable PendingTcSplice | |
Defined in GHC.Hs.Expr Methods ppr :: PendingTcSplice -> SDoc # |
data PendingRnSplice #
Pending Renamer Splice
Constructors
PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn) |
Instances
Outputable PendingRnSplice | |
Defined in GHC.Hs.Expr Methods ppr :: PendingRnSplice -> SDoc # |
data UntypedSpliceFlavour #
Instances
Data UntypedSpliceFlavour | |
Defined in GHC.Hs.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 DelayedSplice #
Instances
Data DelayedSplice | |
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 XBindStmtTc #
Constructors
XBindStmtTc | |
Fields |
data XBindStmtRn #
Constructors
XBindStmtRn | |
Fields |
Constructors
RecStmtTc | |
Fields
|
Instances
Data GrhsAnn | |
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 | |
Defined in GHC.Hs.Expr |
data MatchGroupTc #
Constructors
MatchGroupTc | |
Instances
Data MatchGroupTc | |
Defined in GHC.Hs.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 # |
type CmdSyntaxTable p = [(Name, HsExpr p)] #
Command Syntax Table (for Arrow syntax)
data HsExpansion orig expanded #
Constructors
HsExpanded orig expanded |
Instances
(Data orig, Data expanded) => Data (HsExpansion orig expanded) | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpansion orig expanded -> c (HsExpansion orig expanded) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpansion orig expanded) # toConstr :: HsExpansion orig expanded -> Constr # dataTypeOf :: HsExpansion orig expanded -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpansion orig expanded)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpansion orig expanded)) # gmapT :: (forall b. Data b => b -> b) -> HsExpansion orig expanded -> HsExpansion orig expanded # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpansion orig expanded -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpansion orig expanded -> r # gmapQ :: (forall d. Data d => d -> u) -> HsExpansion orig expanded -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpansion orig expanded -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpansion orig expanded -> m (HsExpansion orig expanded) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpansion orig expanded -> m (HsExpansion orig expanded) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpansion orig expanded -> m (HsExpansion orig expanded) # | |
(Outputable a, Outputable b) => Outputable (HsExpansion a b) | Just print the original expression (the |
Defined in GHC.Hs.Expr Methods ppr :: HsExpansion a b -> SDoc # |
data XXExprGhcTc #
Constructors
WrapExpr !(HsWrap HsExpr) | |
ExpansionExpr !(HsExpansion (HsExpr GhcRn) (HsExpr GhcTc)) | |
ConLikeTc ConLike [TcTyVar] [Scaled TcType] | |
HsTick CoreTickish (LHsExpr GhcTc) | |
HsBinTick Int Int (LHsExpr GhcTc) |
Instances
Outputable XXExprGhcTc | |
Defined in GHC.Hs.Expr Methods ppr :: XXExprGhcTc -> SDoc # |
Constructors
AnnsIf | |
Fields
|
Instances
Data AnnsIf | |
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 | |
Fields
|
Instances
Data AnnProjection | |
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 | |
Fields |
Instances
Data AnnFieldLabel | |
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 #
Constructors
AnnExplicitSum | |
Fields
|
Instances
Data AnnExplicitSum | |
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 # |
data EpAnnUnboundVar #
Constructors
EpAnnUnboundVar | |
Fields |
Instances
Data EpAnnUnboundVar | |
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 #
Constructors
EpAnnHsCase | |
Fields |
Instances
Data EpAnnHsCase | |
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 HsBracketTc #
Constructors
HsBracketTc | |
Fields
|
data HsWrap (hs_syn :: Type -> Type) #
HsWrap appears only in typechecker output
Instances
(Data (hs_syn GhcTc), Typeable hs_syn) => Data (HsWrap hs_syn) | |
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) # |
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.
Constructors
SyntaxExprTc | |
Fields
| |
NoSyntaxExprTc |
Instances
Outputable SyntaxExprTc | |
Defined in GHC.Hs.Expr Methods ppr :: SyntaxExprTc -> SDoc # |
data SyntaxExprRn #
The function to use in rebindable syntax. See Note [NoSyntaxExpr].
Constructors
SyntaxExprRn (HsExpr GhcRn) | |
NoSyntaxExprRn |
Instances
Outputable SyntaxExprRn | |
Defined in GHC.Hs.Expr Methods ppr :: SyntaxExprRn -> SDoc # |
type family SyntaxExprGhc (p :: Pass) = (r :: Type) | r -> p where ... #
Equations
SyntaxExprGhc 'Parsed = NoExtField | |
SyntaxExprGhc 'Renamed = SyntaxExprRn | |
SyntaxExprGhc 'Typechecked = SyntaxExprTc |
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).
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 :: CollectFlag p -> XXPat p -> [IdP p] -> [IdP p] #
collectXXHsBindsLR :: XXHsBindsLR p pR -> [IdP p] -> [IdP p] #
collectXSplicePat :: CollectFlag p -> XSplicePat p -> [IdP p] -> [IdP p] #
Instances
IsPass p => CollectPass (GhcPass p) | |
Defined in GHC.Hs.Utils Methods collectXXPat :: CollectFlag (GhcPass p) -> XXPat (GhcPass p) -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] # collectXXHsBindsLR :: XXHsBindsLR (GhcPass p) pR -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] # collectXSplicePat :: CollectFlag (GhcPass p) -> XSplicePat (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 |
data HsParsedModule #
Constructors
HsParsedModule | |
Fields
|
data AnnsModule #
Constructors
AnnsModule | |
Instances
Data AnnsModule | |
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 | |
Defined in GHC.Hs |
Haskell Module extension point: GHC specific
Constructors
XModulePs | |
Fields
|
Instances
Data XModulePs | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XModulePs -> c XModulePs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XModulePs # toConstr :: XModulePs -> Constr # dataTypeOf :: XModulePs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XModulePs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XModulePs) # gmapT :: (forall b. Data b => b -> b) -> XModulePs -> XModulePs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r # gmapQ :: (forall d. Data d => d -> u) -> XModulePs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> XModulePs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs # |
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 AsPat :: XAsPat p -> LIdP p -> !(LHsToken "@" p) -> LPat p -> Pat p #
As pattern
^ - AnnKeywordId
: AnnAt
pattern ListPat :: XListPat p -> [LPat p] -> Pat p #
Syntactic List
AnnKeywordId
:AnnOpen
'['
,AnnClose
']'
pattern TuplePat :: XTuplePat p -> [LPat p] -> Boxity -> Pat p #
Tuple sub-patterns
AnnKeywordId
:AnnOpen
'('
or'(#'
,AnnClose
')'
or'#)'
pattern SumPat :: XSumPat p -> LPat p -> ConTag -> SumWidth -> Pat p #
Anonymous sum pattern
AnnKeywordId
:AnnOpen
'(#'
,AnnClose
'#)'
pattern ConPat :: XConPat p -> XRec p (ConLikeP p) -> HsConPatDetails p -> Pat p #
Constructor Pattern
Arguments
:: XSplicePat p | |
-> HsUntypedSplice p | Splice Pattern (Includes quasi-quotes) |
-> Pat p |
AnnKeywordId
:AnnOpen
'$('
AnnClose
')'
pattern LitPat :: XLitPat p -> HsLit p -> Pat p #
Literal Pattern Used for *non-overloaded* literal patterns: Int#, Char#, Int, Char, String, etc.
pattern NPat :: XNPat p -> XRec p (HsOverLit p) -> Maybe (SyntaxExpr p) -> SyntaxExpr p -> Pat p #
Natural Pattern
AnnKeywordId
:AnnVal
+
pattern NPlusKPat :: XNPlusKPat p -> LIdP p -> XRec p (HsOverLit p) -> HsOverLit p -> SyntaxExpr p -> SyntaxExpr p -> Pat p #
n+k pattern
Arguments
:: XSigPat p | |
-> LPat p | |
-> HsPatSigType (NoGhcTc p) | Pattern with a type signature |
-> Pat p |
pat_con_ext :: Pat p -> XConPat p #
pat_args :: Pat p -> HsConPatDetails p #
Used when constructing a term with an unused extension point.
dataConCantHappen :: DataConCantHappen -> a #
Eliminate a DataConCantHappen
. See Note [Constructor cannot occur].
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering #
Compares module names lexically, rather than by their Unique
s
moduleNameFS :: ModuleName -> FastString #
moduleNameString :: ModuleName -> String #
mkModuleName :: String -> ModuleName #
mkModuleNameFS :: FastString -> ModuleName #
moduleNameSlashes :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by slashes.
moduleNameColons :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by colons.
pprWithDocString :: HsDocString -> SDoc -> SDoc #
Annotate a pretty printed thing with its doc
The docstring comes after if is HsDocStringPrevious
Otherwise it comes before.
Note - we convert MultiLineDocString HsDocStringPrevious to HsDocStringNext
because we can't control if something else will be pretty printed on the same line
mkHsDocStringChunkUtf8ByteString :: ByteString -> HsDocStringChunk #
Create a HsDocString
from a UTF8-encoded ByteString
.
unpackHDSC :: HsDocStringChunk -> String #
isEmptyDocString :: HsDocString -> Bool #
docStringChunks :: HsDocString -> [LHsDocStringChunk] #
pprHsDocString :: HsDocString -> SDoc #
Pretty print with decorators, exactly as the user wrote it
pprHsDocStrings :: [HsDocString] -> SDoc #
exactPrintHsDocString :: HsDocString -> String #
Pretty print with decorators, exactly as the user wrote it
renderHsDocString :: HsDocString -> String #
Just get the docstring, without any decorators
renderHsDocStrings :: [HsDocString] -> String #
Just get the docstring, without any decorators Separates docstrings using "nn", which is how haddock likes to render them
isPromoted :: PromotionFlag -> Bool #
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Convert a normal annotation into its unicode equivalent one
deltaPos :: Int -> Int -> DeltaPos #
Smart constructor for a DeltaPos
. It preserves the invariant
that for the DifferentLine
constructor deltaLine
is always > 0.
getDeltaLine :: DeltaPos -> Int #
epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan #
Used in the parser only, extract the RealSrcSpan
from an
EpaLocation
. The parser will never insert a DeltaPos
, so the
partial function is safe.
epaLocationFromSrcAnn :: SrcAnn ann -> EpaLocation #
spanAsAnchor :: SrcSpan -> Anchor #
realSpanAsAnchor :: RealSrcSpan -> Anchor #
parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) #
Maps the ParenType
to the related opening and closing
AnnKeywordId. Used when actually printing the item.
trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn #
Convert a TrailingAnn
to an AddEpAnn
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.
addTrailingCommaToN :: SrcSpan -> EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn #
Helper function used in the parser to add a comma location to an existing annotation.
l2n :: LocatedAn a1 a2 -> LocatedN a2 #
Helper function (temporary) during transition of names Discards any annotations
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
l2l :: SrcSpanAnn' a -> SrcAnn ann #
na2la :: SrcSpanAnn' a -> SrcAnn ann #
Helper function (temporary) during transition of names Discards any annotations
realSrcSpan :: SrcSpan -> RealSrcSpan #
srcSpan2e :: SrcSpan -> EpaLocation #
la2e :: SrcSpanAnn' a -> EpaLocation #
extraToAnnList :: AnnList -> [AddEpAnn] -> AnnList #
reAnn :: [TrailingAnn] -> EpAnnComments -> Located a -> LocatedA a #
reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a #
reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e #
getLocAnn :: Located a -> SrcSpanAnnA #
getLocA :: GenLocated (SrcSpanAnn' a) e -> SrcSpan #
noAnnSrcSpan :: SrcSpan -> SrcAnn ann #
noSrcSpanA :: SrcAnn ann #
Short form for EpAnnNotUsed
addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA #
widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan #
The annotations need to all come after the anchor. Make sure this is the case.
widenAnchor :: Anchor -> [AddEpAnn] -> Anchor #
widenAnchorR :: Anchor -> RealSrcSpan -> Anchor #
widenLocatedAn :: SrcSpanAnn' an -> [AddEpAnn] -> SrcSpanAnn' an #
epAnnAnnsL :: EpAnn a -> [a] #
annParen2AddEpAnn :: EpAnn AnnParen -> [AddEpAnn] #
epAnnComments :: EpAnn an -> EpAnnComments #
sortLocatedA :: [GenLocated (SrcSpanAnn' a) e] -> [GenLocated (SrcSpanAnn' a) e] #
mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b #
combineLocsA :: Semigroup a => GenLocated (SrcAnn a) e1 -> GenLocated (SrcAnn a) e2 -> SrcAnn a #
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
addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> e3 -> GenLocated (SrcAnn ann) e3 #
setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments #
setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments #
noComments :: EpAnnCO #
comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO #
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.
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.
addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a #
Add additional comments, 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.
transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #
Transfer comments and trailing items from the annotations in the
first SrcSpanAnnA
argument to those in the second.
commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann #
Remove the exact print annotations payload, leaving only the anchor and comments.
removeCommentsA :: SrcAnn ann -> SrcAnn ann #
Remove the comments, leaving the exact print annotations payload
noHsTok :: forall (tok :: Symbol). GenLocated TokenLocation (HsToken tok) #
noHsUniTok :: forall (tok :: Symbol) (utok :: Symbol). GenLocated TokenLocation (HsUniToken tok utok) #
hsDocIds :: WithHsDocIdentifiers a GhcRn -> NameSet #
Extract a mapping from the lexed identifiers to the names they may correspond to.
pprWithDoc :: LHsDoc name -> SDoc -> SDoc #
Pretty print a thing with its doc The docstring will include the comment decorators '-- |', '{-|' etc and will come either before or after depending on how it was written i.e it will come after the thing if it is a '-- ^' or '{-^' and before otherwise.
pprHsDocDebug :: Outputable (IdP name) => HsDoc name -> SDoc #
Print a doc with its identifiers, useful for debugging
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.
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool #
Convenience function to answer the question if an import decl. is qualified.
ieWrappedLName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> LIdP (GhcPass p) #
ieWrappedName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p) #
lieWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> IdP (GhcPass p) #
ieLWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> LIdP (GhcPass p) #
replaceWrappedName :: IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn #
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc #
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr () pass] #
hsPatSigType :: HsPatSigType pass -> LHsType pass #
mapHsOuterImplicit :: (XHsOuterImplicit pass -> XHsOuterImplicit pass) -> HsOuterTyVarBndrs flag pass -> HsOuterTyVarBndrs flag pass #
hsIPNameFS :: HsIPName -> FastString #
isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool #
Does this HsTyVarBndr
come with an explicit kind annotation?
hsScaledThing :: HsScaled pass a -> a #
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.
hsConPatArgs :: UnXRec p => HsConPatDetails p -> [LPat p] #
hsRecFields :: UnXRec p => HsRecFields p arg -> [XCFieldOcc p] #
hsRecFieldsArgs :: UnXRec p => HsRecFields p arg -> [arg] #
hsRecFieldSel :: UnXRec p => HsRecField p arg -> XCFieldOcc p #
isFixityLSig :: UnXRec p => LSig p -> Bool #
isTypeLSig :: UnXRec p => LSig p -> Bool #
isSpecLSig :: UnXRec p => LSig p -> Bool #
isSpecInstLSig :: UnXRec p => LSig p -> Bool #
isPragLSig :: UnXRec p => LSig p -> Bool #
isInlineLSig :: UnXRec p => LSig p -> Bool #
isMinimalLSig :: UnXRec p => LSig p -> Bool #
isSCCFunSig :: UnXRec p => LSig p -> Bool #
isCompleteMatchSig :: UnXRec p => LSig p -> Bool #
hsGroupInstDecls :: HsGroup id -> [LInstDecl id] #
isDataDecl :: TyClDecl pass -> Bool #
True
= argument is a data
/newtype
declaration.
isClassDecl :: TyClDecl pass -> Bool #
type class
isFamilyDecl :: TyClDecl pass -> Bool #
type/data family declaration
isTypeFamilyDecl :: TyClDecl pass -> Bool #
type family declaration
isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool #
open type family info
isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool #
closed type family info
isDataFamilyDecl :: TyClDecl pass -> Bool #
data family declaration
tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass #
tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass] #
tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass] #
tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass] #
tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass] #
dataDefnConsNewOrData :: DataDefnCons a -> NewOrData #
isTypeDataDefnCons :: DataDefnCons a -> Bool #
Are the constructors within a type data
declaration?
See Note [Type data declarations] in GHC.Rename.Module.
collectRuleBndrSigTys :: [RuleBndr pass] -> [HsPatSigType pass] #
docDeclDoc :: DocDecl pass -> LHsDoc pass #
annProvenanceName_maybe :: UnXRec p => AnnProvenance p -> Maybe (IdP p) #
isInfixMatch :: Match id body -> Bool #
isPatSynCtxt :: HsMatchContext p -> Bool #
isComprehensionContext :: HsStmtContext id -> Bool #
isMonadStmtContext :: HsStmtContext id -> Bool #
Is this a monadic context?
isMonadDoStmtContext :: HsDoFlavour -> Bool #
isMonadCompContext :: HsStmtContext id -> Bool #
isMonadDoCompContext :: HsDoFlavour -> Bool #
pprFunBind :: forall (idR :: Pass). OutputableBndrId idR => MatchGroup (GhcPass idR) (LHsExpr (GhcPass idR)) -> SDoc #
pprPatBind :: forall (bndr :: Pass) (p :: Pass). (OutputableBndrId bndr, OutputableBndrId p) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) (LHsExpr (GhcPass p)) -> SDoc #
pprUntypedSplice :: forall (p :: Pass). OutputableBndrId p => Bool -> Maybe SplicePointName -> HsUntypedSplice (GhcPass p) -> SDoc #
pprTypedSplice :: forall (p :: Pass). OutputableBndrId p => Maybe SplicePointName -> LHsExpr (GhcPass p) -> SDoc #
pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc #
fromMaybeContext :: forall (p :: Pass). Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p) #
mkHsForAllVisTele :: forall (p :: Pass). EpAnnForallTy -> [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p) #
mkHsForAllInvisTele :: forall (p :: Pass). EpAnnForallTy -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p) #
mkHsQTvs :: [LHsTyVarBndr () GhcPs] -> LHsQTyVars GhcPs #
hsSigWcType :: UnXRec p => LHsSigWcType p -> LHsType p #
dropWildCards :: LHsSigWcType pass -> LHsSigType pass #
hsOuterTyVarNames :: HsOuterTyVarBndrs flag GhcRn -> [Name] #
hsOuterExplicitBndrs :: forall flag (p :: Pass). HsOuterTyVarBndrs flag (GhcPass p) -> [LHsTyVarBndr flag (NoGhcTc (GhcPass p))] #
mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs #
mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs] -> HsOuterTyVarBndrs flag GhcPs #
mkHsExplicitSigType :: EpAnnForallTy -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs -> HsSigType GhcPs #
mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing #
mkHsPatSigType :: EpAnnCO -> LHsType GhcPs -> HsPatSigType GhcPs #
mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing #
hsTyVarBndrFlag :: forall flag (pass :: Pass). HsTyVarBndr flag (GhcPass pass) -> flag #
Return the attached flag
setHsTyVarBndrFlag :: forall flag flag' (pass :: Pass). flag -> HsTyVarBndr flag' (GhcPass pass) -> HsTyVarBndr flag (GhcPass pass) #
Set the attached flag
hsTvbAllKinded :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> Bool #
Do all type variables in this LHsQTyVars
come with kind annotations?
hsUnrestricted :: forall a (p :: Pass). a -> HsScaled (GhcPass p) a #
isUnrestricted :: HsArrow GhcRn -> Bool #
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.
pprHsArrow :: forall (pass :: Pass). OutputableBndrId pass => HsArrow (GhcPass pass) -> SDoc #
hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name] #
hsScopedTvs :: LHsSigType GhcRn -> [Name] #
hsTyVarName :: forall flag (p :: Pass). HsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p) #
hsLTyVarName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> IdP (GhcPass p) #
hsLTyVarNames :: forall flag (p :: Pass). [LHsTyVarBndr flag (GhcPass p)] -> [IdP (GhcPass p)] #
hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)] #
hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name] #
hsLTyVarLocName :: forall flag (p :: Pass). LHsTyVarBndr flag (GhcPass p) -> LocatedN (IdP (GhcPass p)) #
hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LocatedN (IdP (GhcPass p))] #
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) ^^^^^^^^
mkHsOpTy :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => PromotionFlag -> LHsType (GhcPass p) -> LocatedN (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p) #
mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
mkHsAppTys :: 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) #
splitHsFunType :: forall (p :: Pass). LHsType (GhcPass p) -> ([AddEpAnn], EpAnnComments, [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p)) #
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.).
lhsTypeArgSrcSpan :: forall (pass :: Pass). LHsTypeArg (GhcPass pass) -> SrcSpan #
Compute the SrcSpan
associated with an LHsTypeArg
.
numVisibleArgs :: [HsArg tm ty] -> Arity #
pprHsArgsApp :: (OutputableBndr id, Outputable tm, Outputable ty) => id -> LexicalFixity -> [HsArg tm ty] -> SDoc #
pretty-prints an application of pprHsArgsApp
id fixity argsid
to args
, using the fixity
to tell whether id
should be printed prefix
or infix. Examples:
pprHsArgsApp T Prefix [HsTypeArg Bool, HsValArg Int] = T @Bool Int pprHsArgsApp T Prefix [HsTypeArg Bool, HsArgPar, HsValArg Int] = (T @Bool) Int pprHsArgsApp (++) Infix [HsValArg Char, HsValArg Double] = Char ++ Double pprHsArgsApp (++) Infix [HsValArg Char, HsValArg Double, HsVarArg Ordering] = (Char ++ Double) Ordering
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.
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 forall
s. 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.
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
areHsOuterExplicit
if the type has explicit, outermost type variable binders. Otherwise, they areHsOuterImplicit
.mb_ctxt
isJust
the context, if it is provided. Otherwise, it isNothing
.body
is the body of the type after the optionalforall
s 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 :: 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 forall
s. 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").
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 forall
s. 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").
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.
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.
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).
rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName #
pprAnonWildCard :: SDoc #
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.
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.
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.
pprLHsContext :: forall (p :: Pass). OutputableBndrId p => Maybe (LHsContext (GhcPass p)) -> SDoc #
pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc #
hsTypeNeedsParens :: forall (p :: Pass). PprPrec -> HsType (GhcPass p) -> Bool #
returns hsTypeNeedsParens
p tTrue
if the type t
needs parentheses
under precedence p
.
parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
checks if parenthesizeHsType
p ty
is
true, and if so, surrounds hsTypeNeedsParens
p tyty
with an HsParTy
. Otherwise, it simply
returns ty
.
parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p) #
checks if parenthesizeHsContext
p ctxtctxt
is a single constraint
c
such that
is true, and if so, surrounds hsTypeNeedsParens
p cc
with an HsParTy
to form a parenthesized ctxt
. Otherwise, it simply
returns ctxt
unchanged.
overLitType :: HsOverLit GhcTc -> Type #
hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool #
returns hsOverLitNeedsParens
p olTrue
if an overloaded literal
ol
needs to be parenthesized under precedence p
.
hsLitNeedsParens :: PprPrec -> HsLit x -> Bool #
returns hsLitNeedsParens
p lTrue
if a literal l
needs
to be parenthesized under precedence p
.
See Note [Printing of literals in Core] in GHC.Types.Literal for the reasoning.
convertLit :: forall (p1 :: Pass) (p2 :: Pass). HsLit (GhcPass p1) -> HsLit (GhcPass p2) #
Convert a literal from one index type to another
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
pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc] #
pprDeclList :: [SDoc] -> SDoc #
emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) #
eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool #
isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool #
emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
emptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR #
isEmptyLHsBinds :: forall (idL :: Pass) idR. LHsBindsLR (GhcPass idL) idR -> Bool #
plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) #
ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc #
isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool #
hasSpecPrags :: TcSpecPrags -> Bool #
isDefaultMethod :: TcSpecPrags -> Bool #
extractSpecPragName :: SourceText -> String #
Extracts the name for a SPECIALIZE instance pragma. In hsSigDoc
, the src
field of SpecInstSig
signature contains the SourceText for a SPECIALIZE
instance pragma of the form: "SourceText {-# SPECIALIZE"
Extraction ensures that all variants of the pragma name (with a Z
or an
S
) are output exactly as used in the pragma.
pragBrackets :: SDoc -> SDoc #
pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc #
Using SourceText in case the pragma was spelled differently or used mixed case
pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc #
pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc #
pprTcSpecPrags :: TcSpecPrags -> SDoc #
pprMinimalSig :: OutputableBndr name => LBooleanFormula (GenLocated l name) -> SDoc #
hsRecFieldId :: HsRecField GhcTc arg -> Id #
hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName #
hsRecUpdFieldId :: HsFieldBind (LAmbiguousFieldOcc GhcTc) arg -> Located Id #
hsRecUpdFieldOcc :: HsFieldBind (LAmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc #
pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc #
pprConArgs :: forall (p :: Pass). (OutputableBndrId p, Outputable (Anno (IdGhcP p))) => HsConPatDetails (GhcPass p) -> SDoc #
mkCharLitPat :: SourceText -> Char -> LPat GhcTc #
looksLazyPatBind :: HsBind GhcTc -> Bool #
isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => DynFlags -> LPat (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)
patNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> Pat (GhcPass p) -> Bool #
returns patNeedsParens
p patTrue
if the pattern pat
needs
parentheses under precedence p
.
gParPat :: forall (pass :: Pass). LPat (GhcPass pass) -> Pat (GhcPass pass) #
Parenthesize a pattern without token information
parenthesizePat :: forall (p :: Pass). IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) #
checks if parenthesizePat
p pat
is true, and
if so, surrounds patNeedsParens
p patpat
with a ParPat
. Otherwise, it simply returns pat
.
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
.
emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
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]
appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p) #
tyFamInstDeclName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyFamInstDecl (GhcPass p) -> IdP (GhcPass p) #
tyFamInstDeclLName :: forall (p :: Pass). Anno (IdGhcP p) ~ SrcSpanAnnN => TyFamInstDecl (GhcPass p) -> LocatedN (IdP (GhcPass p)) #
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) #
hsDeclHasCusk :: TyClDecl GhcRn -> Bool #
Does this declaration have a complete, user-supplied kind signature? See Note [CUSKs: complete user-supplied kind signatures]
pp_vanilla_decl_head :: forall (p :: Pass). OutputableBndrId p => XRec (GhcPass p) (IdP (GhcPass p)) -> LHsQTyVars (GhcPass p) -> LexicalFixity -> Maybe (LHsContext (GhcPass p)) -> SDoc #
familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> XRec (GhcPass p) (IdP (GhcPass p)) #
familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p) #
famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p)) #
resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a)) #
Maybe return name of the result type variable
derivStrategyName :: DerivStrategy a -> SDoc #
A short description of a DerivStrategy'
.
standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p) #
getRecConArgs_maybe :: ConDecl GhcRn -> Maybe (LocatedL [LConDeclField GhcRn]) #
hsConDeclTheta :: forall (p :: Pass). Maybe (LHsContext (GhcPass p)) -> [LHsType (GhcPass p)] #
ppDataDefnHeader :: forall (p :: Pass). OutputableBndrId p => (Maybe (LHsContext (GhcPass p)) -> SDoc) -> HsDataDefn (GhcPass p) -> SDoc #
pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc #
pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc #
pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> HsOuterFamEqnTyVarBndrs (GhcPass p) -> HsTyPats (GhcPass p) -> LexicalFixity -> Maybe (LHsContext (GhcPass p)) -> SDoc #
instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)] #
newOrDataToFlavour :: NewOrData -> TyConFlavour #
Convert a NewOrData
to a TyConFlavour
anyLConIsGadt :: Foldable f => f (GenLocated l (ConDecl pass)) -> Bool #
foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r #
Eliminate a DerivStrategy
.
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.
flattenRuleDecls :: forall (p :: Pass). [LRuleDecls (GhcPass p)] -> [LRuleDecl (GhcPass p)] #
pprFullRuleName :: SourceText -> GenLocated a RuleName -> SDoc #
roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (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)
noSyntaxExpr :: forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p) #
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).
isQuietHsExpr :: HsExpr id -> Bool #
pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc #
ppr_infix_expr_rn :: HsExpansion (HsExpr GhcRn) (HsExpr GhcRn) -> Maybe SDoc #
ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc #
ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc #
pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
hsExprNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> HsExpr (GhcPass p) -> Bool #
returns hsExprNeedsParens
p eTrue
if the expression e
needs
parentheses under precedence p
.
gHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> HsExpr (GhcPass id) #
Parenthesize an expression without token information
parenthesizeHsExpr :: forall (p :: Pass). IsPass p => PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
checks if parenthesizeHsExpr
p e
is true,
and if so, surrounds hsExprNeedsParens
p ee
with an HsPar
. Otherwise, it simply returns e
.
isQuietHsCmd :: HsCmd id -> Bool #
isEmptyMatchGroup :: forall (p :: Pass) body. MatchGroup (GhcPass p) body -> Bool #
isSingletonMatchGroup :: forall (p :: Pass) body. [LMatch (GhcPass p) body] -> Bool #
Is there only one RHS in this list of matches?
matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity #
pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #
pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> 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 #
pp_rhs :: Outputable body => HsMatchContext passL -> 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 #
pprBindStmt :: (Outputable pat, Outputable expr) => pat -> expr -> SDoc #
pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> 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 #
pprBy :: Outputable body => Maybe body -> SDoc #
pprDo :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => HsDoFlavour -> [LStmt (GhcPass p) body] -> SDoc #
pprArrowExpr :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> 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 #
pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc #
pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc #
pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc #
ppr_quasi :: OutputableBndr p => p -> FastString -> SDoc #
ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> Maybe SplicePointName -> LHsExpr (GhcPass p) -> SDoc #
thBrackets :: SDoc -> SDoc -> SDoc #
thTyBrackets :: SDoc -> SDoc #
ppr_with_pending_tc_splices :: SDoc -> [PendingTcSplice] -> SDoc #
lamCaseKeyword :: LamCaseVariant -> SDoc #
pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc #
pprHsArrType :: HsArrAppType -> SDoc #
matchContextErrString :: forall (p :: Pass). OutputableBndrId p => HsMatchContext (GhcPass p) -> SDoc #
pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc #
pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) (ctx :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId ctx, Outputable body, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA) => HsStmtContext (GhcPass ctx) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #
matchSeparator :: HsMatchContext p -> SDoc #
pprMatchContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc #
pprMatchContextNoun :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc #
pprMatchContextNouns :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsMatchContext p -> SDoc #
pprAStmtContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsStmtContext p -> SDoc #
pprStmtContext :: (Outputable (IdP (NoGhcTc p)), UnXRec (NoGhcTc p)) => HsStmtContext p -> SDoc #
pprAHsDoFlavour :: HsDoFlavour -> SDoc #
pprHsDoFlavour :: HsDoFlavour -> SDoc #
prependQualified :: Maybe ModuleName -> SDoc -> SDoc #
pprFieldLabelStrings :: (UnXRec p, Outputable (XRec p FieldLabelString)) => FieldLabelStrings p -> SDoc #
pprPrefixFastString :: FastString -> SDoc #
mkSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns) => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) #
unguardedGRHSs :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => SrcSpan -> LocatedA (body (GhcPass p)) -> EpAnn GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) #
unguardedRHS :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => EpAnn GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) -> [LGRHS (GhcPass p) (LocatedA (body (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))) #
mkLamCaseMatchGroup :: forall (p :: Pass) body. AnnoBody p body => Origin -> LamCaseVariant -> LocatedL [LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))] -> MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) #
mkLocatedList :: Semigroup a => [GenLocated (SrcAnn a) e2] -> LocatedAn an [GenLocated (SrcAnn a) e2] #
mkHsApp :: 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) #
mkHsApps :: forall (id :: Pass). LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
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) #
mkHsLam :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
mkHsCaseAlt :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns, 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
mkLHsPar :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
Wrap in parens if
says it needs them
So hsExprNeedsParens
appPrecf x
becomes (f x)
, but 3
stays as 3
.
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 #
mkHsIntegral :: IntegralLit -> HsOverLit GhcPs #
mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs #
mkHsDoAnns :: HsDoFlavour -> LocatedL [ExprLStmt GhcPs] -> EpAnn AnnList -> HsExpr GhcPs #
mkHsCompAnns :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> EpAnn AnnList -> HsExpr GhcPs #
mkNPat :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpAnn [AddEpAnn] -> Pat GhcPs #
mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpAnn EpaLocation -> Pat GhcPs #
mkTransformStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkTransformByStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkGroupUsingStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkGroupByUsingStmt :: EpAnn [AddEpAnn] -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkLastStmt :: forall (idR :: Pass) bodyR (idL :: Pass). IsPass idR => LocatedA (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (LocatedA (bodyR (GhcPass idR))) #
mkBodyStmt :: forall bodyR (idL :: Pass). LocatedA (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (LocatedA (bodyR GhcPs)) #
mkPsBindStmt :: EpAnn [AddEpAnn] -> LPat GhcPs -> LocatedA (bodyR GhcPs) -> StmtLR GhcPs GhcPs (LocatedA (bodyR GhcPs)) #
mkRnBindStmt :: LPat GhcRn -> LocatedA (bodyR GhcRn) -> StmtLR GhcRn GhcRn (LocatedA (bodyR GhcRn)) #
mkTcBindStmt :: LPat GhcTc -> LocatedA (bodyR GhcTc) -> StmtLR GhcTc GhcTc (LocatedA (bodyR GhcTc)) #
emptyRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => StmtLR (GhcPass idL) GhcPs bodyR #
emptyRecStmtName :: Anno [GenLocated (Anno (StmtLR GhcRn GhcRn bodyR)) (StmtLR GhcRn GhcRn bodyR)] ~ SrcSpanAnnL => StmtLR GhcRn GhcRn bodyR #
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.
mkHsStringFS :: forall (p :: Pass). FastString -> HsLit (GhcPass p) #
mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p) #
mkConLikeTc :: ConLike -> HsExpr GhcTc #
nlHsApp :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
nlHsSyntaxApps :: SyntaxExprTc -> [LHsExpr GhcTc] -> LHsExpr GhcTc #
nlHsApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [LHsExpr (GhcPass p)] -> LHsExpr (GhcPass p) #
nlHsVarApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [IdP (GhcPass p)] -> LHsExpr (GhcPass p) #
nlNullaryConPat :: RdrName -> LPat GhcPs #
nlWildConPat :: DataCon -> LPat GhcPs #
nlWildPatName :: LPat GhcRn #
Wildcard pattern - after renaming
nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsTyVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> IdP (GhcPass p) -> LHsType (GhcPass p) #
nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsTyConApp :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> LexicalFixity -> IdP (GhcPass p) -> [LHsTypeArg (GhcPass p)] -> LHsType (GhcPass p) #
nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p) #
mkLHsTupleExpr :: forall (p :: Pass). [LHsExpr (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) #
mkLHsVarTuple :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) #
missingTupArg :: EpAnn EpaLocation -> HsTupArg 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
mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> XExplicitTuple (GhcPass id) -> LHsExpr (GhcPass id) #
hsTypeToHsSigType :: LHsType GhcPs -> LHsSigType GhcPs #
Convert an LHsType
to an LHsSigType
.
hsTypeToHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs #
Convert an LHsType
to an LHsSigWcType
.
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
mkHsWrapCo :: TcCoercionN -> HsExpr GhcTc -> HsExpr GhcTc #
mkHsWrapCoR :: TcCoercionR -> HsExpr GhcTc -> HsExpr GhcTc #
mkLHsWrapCo :: TcCoercionN -> LHsExpr GhcTc -> LHsExpr GhcTc #
mkHsWrapPatCo :: TcCoercionN -> Pat GhcTc -> Type -> Pat GhcTc #
mkFunBind :: Origin -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs #
Not infix, with place holders for coercion and free vars
mkTopFunBind :: Origin -> LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn #
In Name-land, with empty bind_fvs
mkPatSynBind :: LocatedN RdrName -> HsPatSynDetails GhcPs -> LPat GhcPs -> HsPatSynDir GhcPs -> EpAnn [AddEpAnn] -> HsBind GhcPs #
isInfixFunBind :: forall id1 id2. UnXRec id2 => HsBindLR id1 id2 -> Bool #
spanHsLocaLBinds :: forall (p :: Pass). HsLocalBinds (GhcPass p) -> SrcSpan #
Return the SrcSpan
encompassing the contents of any enclosed binds
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.
mkPrefixFunRhs :: LIdP (NoGhcTc p) -> HsMatchContext p #
Make a prefix, non-strict function HsMatchContext
mkMatch :: forall (p :: Pass). IsPass p => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> HsLocalBinds (GhcPass p) -> LMatch (GhcPass p) (LHsExpr (GhcPass p)) #
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.
isBangedHsBind :: HsBind GhcTc -> Bool #
Is a binding a strict variable or pattern bind (e.g. !x = ...
)?
collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsLocalBindsLR (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)] #
collectHsValBinders :: forall (idL :: Pass) idR. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) idR -> [IdP (GhcPass idL)] #
collectHsBindBinders :: CollectPass p => CollectFlag p -> HsBindLR p idR -> [IdP p] #
Collect both Id
s and pattern-synonym binders
collectHsBindsBinders :: CollectPass p => CollectFlag p -> LHsBindsLR p idR -> [IdP p] #
collectHsBindListBinders :: CollectPass p => CollectFlag p -> [LHsBindLR p idR] -> [IdP p] #
Same as collectHsBindsBinders
, but works over a list of bindings
collectMethodBinders :: UnXRec idL => LHsBindsLR idL idR -> [LIdP idL] #
Used exclusively for the bindings of an instance decl which are all
FunBinds
collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #
collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [StmtLR (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)] #
collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #
collectPatBinders :: CollectPass p => CollectFlag p -> LPat p -> [IdP p] #
collectPatsBinders :: CollectPass p => CollectFlag p -> [LPat p] -> [IdP p] #
hsGroupBinders :: HsGroup GhcRn -> [Name] #
hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name] #
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]
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
.
getPatSynBinds :: UnXRec id => [(RecFlag, LHsBinds id)] -> [PatSynBind id id] #
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
lStmtsImplicits :: forall (idR :: Pass) (body :: Type -> Type). [LStmtLR GhcRn (GhcPass idR) (LocatedA (body (GhcPass idR)))] -> [(SrcSpan, [Name])] #
hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])] #
Name OccName GHC.Types.Name
nameOccName :: Name -> OccName #
occName :: HasOccName name => name -> OccName #
occNameString :: OccName -> String #
ppr :: Outputable a => a -> SDoc #
Outputable / GHC.Utils.Outputable
showSDocUnsafe :: SDoc -> String #
Panic / GHC.Utils.Panic
handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a #
RdrName / GHC.Types.Name.Reader
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` ( ~ )
AnnKeywordId
:AnnType
,AnnOpen
'('
or'['
or'[:'
,AnnClose
')'
or']'
or':]'
,,AnnBackquote
'`'
,AnnVal
AnnTilde
,
Constructors
Unqual OccName | Unqualified name Used for ordinary, unqualified occurrences, e.g. |
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 |
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 |
Exact Name | Exact name We know exactly the
Such a |
Instances
rdrNameOcc :: RdrName -> OccName #
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
pattern RealSrcLoc' :: RealSrcLoc -> SrcLoc Source #
pattern RealSrcSpan' :: RealSrcSpan -> SrcSpan Source #
data RealSrcSpan #
A RealSrcSpan
delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.
Real Source Span
Instances
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.
composeSrcSpan :: a -> a Source #
decomposeSrcSpan :: a -> a Source #
StringBuffer
stringToStringBuffer :: String -> StringBuffer #
Encode a String
into a StringBuffer
as UTF-8. The resulting buffer
is automatically managed by the garbage collector.
Misc
impliedXFlags :: [(Extension, TurnOnFlag, Extension)] #
Non-GHC stuff
type FunBind = HsMatchContext GhcPs Source #
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 MonadFail' = MonadFail Source #
type ReplaceWorker a mod = (Data a, Data mod) => mod -> Parser (LocatedA a) -> Int -> Refactoring SrcSpan -> IO mod Source #
annSpanToSrcSpan :: AnnSpan -> SrcSpan Source #
badAnnSpan :: AnnSpan Source #
parseModuleName :: SrcSpan -> Parser (LocatedA ModuleName) Source #
setAnnSpanFile :: FastString -> AnnSpan -> AnnSpan Source #
setSrcSpanFile :: FastString -> SrcSpan -> SrcSpan Source #
srcSpanToAnnSpan :: SrcSpan -> AnnSpan Source #
type AnnSpan = RealSrcSpan Source #
commentSrcSpan :: LEpaComment -> SrcSpan Source #
ann :: SrcSpanAnn' a -> a Source #
transferEntryDP :: forall (m :: Type -> Type) t2 t1 a b. (Monad m, Monoid t2, Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> TransformT m (LocatedAn t2 b) #
Take the annEntryDelta associated with the first item and associate it with the second. Also transfer any comments occuring before it.
transferEntryDP' :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs) #
Take the annEntryDelta associated with the first item and associate it with the second. Also transfer any comments occuring before it. TODO: call transferEntryDP, and use pushDeclDP
type AnnConstraint an = Monoid an Source #
GHC 9.4 stuff
initParserOpts :: DynFlags -> ParserOpts #
Extracts the flags needed for parsing