ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Tc.Types.ErrCtxt

Synopsis

Documentation

type ErrCtxt = (Bool, TidyEnv -> ZonkM (TidyEnv, ErrCtxtMsg)) Source #

Additional context to include in an error message, e.g. "In the type signature ...", "In the ambiguity check for ...", etc.

data ErrCtxtMsg Source #

The "context" of an error message, e.g. "In the expression ...", "In the pattern ...", or "In the equations for closed type family ...".

Constructors

ExprCtxt !(HsExpr GhcRn)

In an expression.

ThetaCtxt !UserTypeCtxt !ThetaType

In a user-written context.

QuantifiedCtCtxt !PredType

In a quantified constraint.

InferredTypeCtxt !Name !TcType

When checking an inferred type.

SigCtxt !(Sig GhcRn)

In an inline pragma, or a fixity signature, or a type signature, or... (see Sig).

UserSigCtxt !UserTypeCtxt !(UserSigType GhcRn)

In a user-written type signature.

RecordUpdCtxt !(NonEmpty ConLike) ![Name] ![TyCoVar]

In a record update.

ClassOpCtxt !Id !Type

In a class method.

MethSigCtxt !Name !TcType !TcType

In the instance type signature of a class method.

PatSigErrCtxt !TcType !TcType

In a pattern type signature.

PatCtxt !(Pat GhcRn)

In a pattern.

PatSynDeclCtxt !Name

In a pattern synonym declaration.

MatchCtxt !HsMatchContextRn

In a pattern matching context, e.g. a equation for a function binding, or a case alternative, ...

Outputable body => MatchInCtxt !(Match GhcRn body)

In a match in a pattern matching context, either for an expression or for an arrow command.

FunAppCtxt !FunAppCtxtFunArg !Int

In a function application.

FunTysCtxt !ExpectedFunTyOrigin !Type !Int !Int

In a function call.

FunResCtxt !(HsExpr GhcTc) !Int !Type !Type !Int !Int

In the result of a function call.

TyConDeclCtxt !Name !(TyConFlavour TyCon)

In the declaration of a type constructor.

TyConInstCtxt !Name !TyConInstFlavour

In a type or data family instance (or default instance).

DataConDefCtxt !(NonEmpty (LocatedN Name))

In the declaration of a data constructor.

DataConResTyCtxt !(NonEmpty (LocatedN Name))

In the result type of a data constructor.

ClosedFamEqnCtxt !TyCon

In the equations for a closed type family.

TySynErrCtxt !TyCon

In the expansion of a type synonym.

RoleAnnotErrCtxt !Name

In a role annotation.

CmdCtxt !(HsCmd GhcRn)

In an arrow command.

InstDeclErrCtxt !(Either (LHsType GhcRn) PredType)

In an instance declaration.

DefaultDeclErrCtxt

In a default declaration.

StaticFormCtxt !(LHsExpr GhcRn)

In the body of a static form.

OutputableBndrId p => PatMonoBindsCtxt !(LPat (GhcPass p)) !(GRHSs GhcRn (LHsExpr GhcRn))

In a pattern binding.

ForeignDeclCtxt !(ForeignDecl GhcRn)

In a foreign import/export declaration.

FieldCtxt !FieldLabelString

In a record field.

TypeCtxt !(LHsType GhcRn)

In a type.

KindCtxt !(LHsKind GhcRn)

In a kind.

AmbiguityCheckCtxt !UserTypeCtxt !Bool

In an ambiguity check.

TermLevelUseCtxt !Name !TermLevelUseCtxt

In a term-level use of a Name.

MainCtxt !Name

When checking the type of the main function.

VDQWarningCtxt !TcTyCon

Warning emitted when inferring use of visible dependent quantification.

(Anno (StmtLR GhcRn GhcRn body) ~ SrcSpanAnnA, Outputable body) => StmtErrCtxt !HsStmtContextRn !(StmtLR GhcRn GhcRn body)

In a statement.

SyntaxNameCtxt !(HsExpr GhcRn) !CtOrigin !TcType !SrcSpan

In an rebindable syntax expression.

RuleCtxt !FastString

In a RULE.

SubTypeCtxt !TcType !TcType

In a subtype check.

OutputableBndrId p => ExportCtxt (IE (GhcPass p))

In an export.

PatSynExportCtxt !PatSyn

In an export of a pattern synonym.

PatSynRecSelExportCtxt !PatSyn !Name

In an export of a pattern synonym record field.

OutputableBndrId p => AnnCtxt (AnnDecl (GhcPass p))

In an annotation.

SpecPragmaCtxt !(Sig GhcRn)

In a specialise pragma.

DerivInstCtxt !PredType

In a deriving clause.

StandaloneDerivCtxt !(LHsSigWcType GhcRn)

In a standalone deriving clause.

DerivBindCtxt !Id !Class ![Type]

When typechecking the body of a derived instance.

UntypedTHBracketCtxt !(HsQuote GhcPs)

In an untyped Template Haskell quote.

OutputableBndrId p => TypedTHBracketCtxt !(LHsExpr (GhcPass p))

In a typed Template Haskell quote.

UntypedSpliceCtxt !(HsUntypedSplice GhcPs)

In an untyped Template Haskell splice or quasi-quote.

OutputableBndrId p => TypedSpliceCtxt !(Maybe SplicePointName) !(LHsExpr (GhcPass p))

In a typed TEmplate Haskell splice.

TypedSpliceResultCtxt !(LHsExpr GhcTc)

In the result of a typed Template Haskell splice.

ReifyInstancesCtxt !Name ![Type]

In an argument to the Template Haskell reifyInstances function.

MergeSignaturesCtxt !UnitState !ModuleName ![InstantiatedModule]

While merging Backpack signatures.

CheckImplementsCtxt !UnitState !Module !InstantiatedModule

While checking that a module implements a Backpack signature.

data UserSigType p Source #

Constructors

UserLHsSigType !(LHsSigType p) 
UserLHsType !(LHsType p) 

Instances

Instances details
OutputableBndrId p => Outputable (UserSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Tc.Types.ErrCtxt

Methods

ppr :: UserSigType (GhcPass p) -> SDoc Source #

data TyConInstFlavour Source #

Like TyConFlavour but for instance declarations, with the additional information of whether this we are dealing with a default declaration.