ghc-9.2.3: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Tc.Types.Origin

Description

Describes the provenance of types as they flow through the type-checker. The datatypes here are mainly used for error message generation.

Synopsis

Documentation

data CtOrigin Source #

Constructors

GivenOrigin SkolemInfo

A given constraint from a user-written type signature. The SkolemInfo inside gives more information.

InstSCOrigin

InstSCOrigin is used for a Given constraint obtained by superclass selection from the context of an instance declaration. E.g. instance (Foo a, Bar a) => C [a] where ... When typechecking the instance decl itself, including producing evidence for the superclasses of C, the superclasses of (Foo a) and (Bar a) will have InstSCOrigin origin.

Fields

  • ScDepth

    The number of superclass selections necessary to get this constraint; see Note [Replacement vs keeping] and Note [Use only the best local instance], both in GHC.Tc.Solver.Interact

  • TypeSize

    If (C ty1 .. tyn) is the largest class from which we made a superclass selection in the chain, then TypeSize = sizeTypes [ty1, .., tyn] See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance

OtherSCOrigin

OtherSCOrigin is used for a Given constraint obtained by superclass selection from a constraint other than the context of an instance declaration. (For the latter we use InstSCOrigin.) E.g. f :: Foo a => blah f = e When typechecking body of f, the superclasses of the Given (Foo a) will have OtherSCOrigin. Needed for Note [Replacement vs keeping] and Note [Use only the best local instance], both in GHC.Tc.Solver.Interact.

Fields

  • ScDepth

    The number of superclass selections necessary to get this constraint

  • SkolemInfo

    Where the sub-class constraint arose from (used only for printing)

OccurrenceOf Name 
OccurrenceOfRecSel RdrName 
AppOrigin 
SpecPragOrigin UserTypeCtxt 
TypeEqOrigin 

Fields

KindEqOrigin TcType TcType CtOrigin (Maybe TypeOrKind) 
IPOccOrigin HsIPName 
OverLabelOrigin FastString 
LiteralOrigin (HsOverLit GhcRn) 
NegateOrigin 
ArithSeqOrigin (ArithSeqInfo GhcRn) 
AssocFamPatOrigin 
SectionOrigin 
HasFieldOrigin FastString 
TupleOrigin 
ExprSigOrigin 
PatSigOrigin 
PatOrigin 
ProvCtxtOrigin (PatSynBind GhcRn GhcRn) 
RecordUpdOrigin 
ViewPatOrigin 
ScOrigin TypeSize

ScOrigin is used only for the Wanted constraints for the superclasses of an instance declaration. If the instance head is C ty1 .. tyn then TypeSize = sizeTypes [ty1, .., tyn] See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance

DerivClauseOrigin 
DerivOriginDC DataCon Int Bool 
DerivOriginCoerce Id Type Type Bool 
StandAloneDerivOrigin 
DefaultOrigin 
DoOrigin 
DoPatOrigin (LPat GhcRn) 
MCompOrigin 
MCompPatOrigin (LPat GhcRn) 
IfOrigin 
ProcOrigin 
AnnOrigin 
FunDepOrigin1 PredType CtOrigin RealSrcSpan PredType CtOrigin RealSrcSpan 
FunDepOrigin2 PredType CtOrigin PredType SrcSpan 
ExprHoleOrigin OccName 
TypeHoleOrigin OccName 
PatCheckOrigin 
ListOrigin 
BracketOrigin 
StaticOrigin 
Shouldn'tHappenOrigin String 
InstProvidedOrigin Module ClsInst 
NonLinearPatternOrigin 
UsageEnvironmentOf Name 
CycleBreakerOrigin CtOrigin 

Instances

Instances details
Outputable CtOrigin Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: CtOrigin -> SDoc Source #

lexprCtOrigin :: LHsExpr GhcRn -> CtOrigin Source #

Extract a suitable CtOrigin from a HsExpr

matchesCtOrigin :: MatchGroup GhcRn (LHsExpr GhcRn) -> CtOrigin Source #

Extract a suitable CtOrigin from a MatchGroup

grhssCtOrigin :: GRHSs GhcRn (LHsExpr GhcRn) -> CtOrigin Source #

Extract a suitable CtOrigin from guarded RHSs