GHC.Tc.Types.Constraint
This module defines types and simple operations over constraints, as used in the type-checker and constraint solver.
Documentation
Constructors
QCI | |
Fields
|
Instances
Constructors
CDictCan | |
Fields
| |
CIrredCan | |
Fields | |
CEqCan | |
CNonCanonical | |
Fields
| |
CQuantCan QCInst |
Instances
andManyCts :: [Cts] -> Cts Source #
isEmptyCts :: Cts -> Bool Source #
isPendingScDict :: Ct -> Bool Source #
superClassesMightHelp :: WantedConstraints -> Bool Source #
True if taking superclasses of givens, or of wanteds (to perhaps expose more equalities or functional dependencies) might help to solve this constraint. See Note [When superclasses help]
isWantedCt :: Ct -> Bool Source #
isUserTypeError :: PredType -> Bool Source #
getUserTypeErrorMsg :: PredType -> Maybe Type Source #
A constraint is considered to be a custom type error, if it contains custom type errors anywhere in it. See Note [Custom type errors in constraints]
ctEvidence :: Ct -> CtEvidence Source #
ctRewriters :: Ct -> RewriterSet Source #
mkTcEqPredLikeEv :: CtEvidence -> TcType -> TcType -> TcType Source #
Makes a new equality predicate with the same role as the given evidence.
mkNonCanonical :: CtEvidence -> Ct Source #
mkNonCanonicalCt :: Ct -> Ct Source #
mkIrredCt :: CtIrredReason -> CtEvidence -> Ct Source #
ctEvPred :: CtEvidence -> TcPredType Source #
ctEvLoc :: CtEvidence -> CtLoc Source #
ctEvOrigin :: CtEvidence -> CtOrigin Source #
ctEvEqRel :: CtEvidence -> EqRel Source #
Get the equality relation relevant for a CtEvidence
ctEvExpr :: HasDebugCallStack => CtEvidence -> EvExpr Source #
ctEvTerm :: CtEvidence -> EvTerm Source #
ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion Source #
ctEvEvId :: CtEvidence -> EvVar Source #
ctEvRewriters :: CtEvidence -> RewriterSet Source #
Extract the set of rewriters from a CtEvidence
See Note [Wanteds rewrite Wanteds]
If the provided CtEvidence is not for a Wanted, just
return an empty set.
tyCoVarsOfCt :: Ct -> TcTyCoVarSet Source #
Returns free variables of constraints as a non-deterministic set
tyCoVarsOfCts :: Cts -> TcTyCoVarSet Source #
Returns free variables of a bag of constraints as a non-deterministic set. See Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfCtList :: Ct -> [TcTyCoVar] Source #
Returns free variables of constraints as a deterministically ordered list. See Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfCtsList :: Cts -> [TcTyCoVar] Source #
Returns free variables of a bag of constraints as a deterministically ordered list. See Note [Deterministic FV] in GHC.Utils.FV.
data CtIrredReason Source #
Used to indicate extra information about why a CIrredCan is irreducible
Constructors
IrredShapeReason | this constraint has a non-canonical shape (e.g. |
NonCanonicalReason CheckTyEqResult | an equality where some invariant other than (TyEq:H) of |
ReprEqReason | an equality that cannot be decomposed because it is representational.
Example: |
ShapeMismatchReason | a nominal equality that relates two wholly different types,
like |
AbstractTyConReason | an equality like |
Instances
Outputable CtIrredReason Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: CtIrredReason -> SDoc Source # |
isInsolubleReason :: CtIrredReason -> Bool Source #
Are we sure that more solving will never solve this constraint?
data CheckTyEqResult Source #
A set of problems in checking the validity of a type equality.
See checkTypeEq
.
Instances
Monoid CheckTyEqResult Source # | |
Defined in GHC.Tc.Types.Constraint Methods mempty :: CheckTyEqResult Source # mappend :: CheckTyEqResult -> CheckTyEqResult -> CheckTyEqResult Source # mconcat :: [CheckTyEqResult] -> CheckTyEqResult Source # | |
Semigroup CheckTyEqResult Source # | |
Defined in GHC.Tc.Types.Constraint Methods (<>) :: CheckTyEqResult -> CheckTyEqResult -> CheckTyEqResult Source # sconcat :: NonEmpty CheckTyEqResult -> CheckTyEqResult Source # stimes :: Integral b => b -> CheckTyEqResult -> CheckTyEqResult Source # | |
Outputable CheckTyEqResult Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: CheckTyEqResult -> SDoc Source # |
data CheckTyEqProblem Source #
An individual problem that might be logged in a CheckTyEqResult
cteOK :: CheckTyEqResult Source #
No problems in checking the validity of a type equality.
cterSetOccursCheckSoluble :: CheckTyEqResult -> CheckTyEqResult Source #
Mark a CheckTyEqResult
as not having an insoluble occurs-check: any occurs
check under a type family or in a representation equality is soluble.
cterHasNoProblem :: CheckTyEqResult -> Bool Source #
Check whether a CheckTyEqResult
is marked successful.
cterHasProblem :: CheckTyEqResult -> CheckTyEqProblem -> Bool Source #
Check whether a CheckTyEqResult
has a CheckTyEqProblem
cterHasOnlyProblem :: CheckTyEqResult -> CheckTyEqProblem -> Bool Source #
Check whether a CheckTyEqResult
has one CheckTyEqProblem
and no other
cterFromKind :: CheckTyEqResult -> CheckTyEqResult Source #
Retain only information about occurs-check failures, because only that matters after recurring into a kind.
A CanEqLHS
is a type that can appear on the left of a canonical
equality: a type variable or exactly-saturated type family application.
Instances
canEqLHS_maybe :: Xi -> Maybe CanEqLHS Source #
Is a type a canonical LHS? That is, is it a tyvar or an exactly-saturated type family application? Does not look through type synonyms.
A hole stores the information needed to report diagnostics about holes in terms (unbound identifiers or underscores) or in types (also called wildcards, as used in partial type signatures). See Note [Holes].
Constructors
Hole | |
Instances
Used to indicate which sort of hole we have.
Constructors
ExprHole HoleExprRef | Either an out-of-scope variable or a "true" hole in an expression (TypedHoles). The HoleExprRef says where to write the the erroring expression for -fdefer-type-errors. |
TypeHole | A hole in a type (PartialTypeSignatures) |
ConstraintHole | A hole in a constraint, like @f :: (_, Eq a) => ... Differentiated from TypeHole because a ConstraintHole is simplified differently. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. |
Instances
isOutOfScopeHole :: Hole -> Bool Source #
Does this hole represent an "out of scope" error? See Note [Insoluble holes]
data DelayedError Source #
A delayed error, to be reported after constraint solving, in order to benefit from deferred unifications.
Constructors
DE_Hole Hole | A hole (in a type or in a term). See Note [Holes]. |
DE_NotConcrete NotConcreteError | A type could not be ensured to be concrete. See Note [The Concrete mechanism] in GHC.Tc.Utils.Concrete. |
Instances
Outputable DelayedError Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: DelayedError -> SDoc Source # |
data NotConcreteError Source #
Why did we require that a certain type be concrete?
Constructors
NCE_FRR | Concreteness was required by a representation-polymorphism check. See Note [The Concrete mechanism] in GHC.Tc.Utils.Concrete. |
Fields
|
Instances
Outputable NotConcreteError Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: NotConcreteError -> SDoc Source # |
data NotConcreteReason Source #
Why did we decide that a type was not concrete?
Constructors
NonConcreteTyCon TyCon [TcType] | The type contains a See Note [Concrete types] in GHC.Tc.Utils.Concrete. |
NonConcretisableTyVar TyVar | The type contains a type variable that could not be made concrete (e.g. a skolem type variable). |
ContainsCast TcType TcCoercionN | The type contains a cast. |
ContainsForall TyCoVarBinder TcType | The type contains a forall. |
ContainsCoercionTy TcCoercion | The type contains a |
data WantedConstraints Source #
Constructors
WC | |
Fields
|
Instances
Outputable WantedConstraints Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: WantedConstraints -> SDoc Source # |
insolubleWC :: WantedConstraints -> Bool Source #
isEmptyWC :: WantedConstraints -> Bool Source #
isSolvedWC :: WantedConstraints -> Bool Source #
Checks whether a the given wanted constraints are solved, i.e. that there are no simple constraints left and all the implications are solved.
mkSimpleWC :: [CtEvidence] -> WantedConstraints Source #
addInsols :: WantedConstraints -> Bag Ct -> WantedConstraints Source #
addSimples :: WantedConstraints -> Bag Ct -> WantedConstraints Source #
addHoles :: WantedConstraints -> Bag Hole -> WantedConstraints Source #
tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet Source #
Returns free variables of WantedConstraints as a non-deterministic set. See Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] Source #
Returns free variables of WantedConstraints as a deterministically ordered list. See Note [Deterministic FV] in GHC.Utils.FV.
insolubleWantedCt :: Ct -> Bool Source #
insolubleEqCt :: Ct -> Bool Source #
insolubleCt :: Ct -> Bool Source #
Returns True of equality constraints that are definitely insoluble,
as well as TypeError constraints.
Can return True
for Given constraints, unlike insolubleWantedCt
.
This function is critical for accurate pattern-match overlap warnings. See Note [Pattern match warnings with insoluble Givens] in GHC.Tc.Solver
Note that this does not traverse through the constraint to find
nested custom type errors: it only detects TypeError msg :: Constraint
,
and not e.g. Eq (TypeError msg)
.
insolubleImplic :: Implication -> Bool Source #
nonDefaultableTyVarsOfWC :: WantedConstraints -> TyCoVarSet Source #
Gather all the type variables from WantedConstraints
that it would be unhelpful to default. For the moment,
these are only ConcreteTv
metavariables participating
in a nominal equality whose other side is not concrete;
it's usually better to report those as errors instead of
defaulting.
data Implication Source #
Constructors
Implic | |
Fields
|
Instances
Outputable Implication Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: Implication -> SDoc Source # |
data ImplicStatus Source #
Constructors
IC_Solved | |
IC_Insoluble | |
IC_BadTelescope | |
IC_Unsolved |
Instances
Outputable ImplicStatus Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: ImplicStatus -> SDoc Source # |
isInsolubleStatus :: ImplicStatus -> Bool Source #
isSolvedStatus :: ImplicStatus -> Bool Source #
type UserGiven = Implication Source #
getUserGivensFromImplics :: [Implication] -> [UserGiven] Source #
data HasGivenEqs Source #
Constructors
NoGivenEqs | |
LocalGivenEqs | |
MaybeGivenEqs |
Instances
Monoid HasGivenEqs Source # | |
Defined in GHC.Tc.Types.Constraint Methods mempty :: HasGivenEqs Source # mappend :: HasGivenEqs -> HasGivenEqs -> HasGivenEqs Source # mconcat :: [HasGivenEqs] -> HasGivenEqs Source # | |
Semigroup HasGivenEqs Source # | |
Defined in GHC.Tc.Types.Constraint Methods (<>) :: HasGivenEqs -> HasGivenEqs -> HasGivenEqs Source # sconcat :: NonEmpty HasGivenEqs -> HasGivenEqs Source # stimes :: Integral b => b -> HasGivenEqs -> HasGivenEqs Source # | |
Outputable HasGivenEqs Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: HasGivenEqs -> SDoc Source # | |
Eq HasGivenEqs Source # | |
Defined in GHC.Tc.Types.Constraint |
checkImplicationInvariants :: (HasCallStack, Applicative m) => Implication -> m () Source #
data SubGoalDepth Source #
See Note [SubGoalDepth]
Instances
Outputable SubGoalDepth Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: SubGoalDepth -> SDoc Source # | |
Eq SubGoalDepth Source # | |
Defined in GHC.Tc.Types.Constraint | |
Ord SubGoalDepth Source # | |
Defined in GHC.Tc.Types.Constraint Methods compare :: SubGoalDepth -> SubGoalDepth -> Ordering # (<) :: SubGoalDepth -> SubGoalDepth -> Bool # (<=) :: SubGoalDepth -> SubGoalDepth -> Bool # (>) :: SubGoalDepth -> SubGoalDepth -> Bool # (>=) :: SubGoalDepth -> SubGoalDepth -> Bool # max :: SubGoalDepth -> SubGoalDepth -> SubGoalDepth # min :: SubGoalDepth -> SubGoalDepth -> SubGoalDepth # |
subGoalDepthExceeded :: DynFlags -> SubGoalDepth -> Bool Source #
Constructors
CtLoc | |
Fields
|
ctLocSpan :: CtLoc -> RealSrcSpan Source #
ctLocLevel :: CtLoc -> TcLevel Source #
ctLocOrigin :: CtLoc -> CtOrigin Source #
ctLocDepth :: CtLoc -> SubGoalDepth Source #
bumpCtLocDepth :: CtLoc -> CtLoc Source #
isGivenLoc :: CtLoc -> Bool Source #
setCtLocSpan :: CtLoc -> RealSrcSpan -> CtLoc Source #
data CtEvidence Source #
Constructors
CtGiven | |
CtWanted | |
Fields
|
Instances
Outputable CtEvidence Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: CtEvidence -> SDoc Source # |
A place for type-checking evidence to go after it is generated.
- Wanted equalities use HoleDest,
- other Wanteds use EvVarDest.
Constructors
EvVarDest EvVar | bind this var to the evidence EvVarDest is always used for non-type-equalities e.g. class constraints |
HoleDest CoercionHole | fill in this hole with the evidence HoleDest is always used for type-equalities See Note [Coercion holes] in GHC.Core.TyCo.Rep |
Instances
mkGivenLoc :: TcLevel -> SkolemInfoAnon -> TcLclEnv -> CtLoc Source #
isWanted :: CtEvidence -> Bool Source #
isGiven :: CtEvidence -> Bool Source #
ctEvRole :: CtEvidence -> Role Source #
Get the role relevant for a CtEvidence
setCtEvPredType :: HasDebugCallStack => CtEvidence -> Type -> CtEvidence Source #
Set the type of CtEvidence.
This function ensures that the invariants on CtEvidence
hold, by updating
the evidence and the ctev_pred in sync with each other.
See Note [CtEvidence invariants].
setCtEvLoc :: CtEvidence -> CtLoc -> CtEvidence Source #
arisesFromGivens :: Ct -> Bool Source #
tyCoVarsOfCtEvList :: CtEvidence -> [TcTyCoVar] Source #
Returns free variables of constraints as a deterministically ordered list. See Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfCtEv :: CtEvidence -> TcTyCoVarSet Source #
Returns free variables of constraints as a non-deterministic set
tyCoVarsOfCtEvsList :: [CtEvidence] -> [TcTyCoVar] Source #
Returns free variables of a bag of constraints as a deterministically ordered list. See Note [Deterministic FV] in GHC.Utils.FV.
ctEvUnique :: CtEvidence -> Unique Source #
tcEvDestUnique :: TcEvDest -> Unique Source #
newtype RewriterSet Source #
Stores a set of CoercionHoles that have been used to rewrite a constraint. See Note [Wanteds rewrite Wanteds].
Constructors
RewriterSet (UniqSet CoercionHole) |
Instances
Monoid RewriterSet Source # | |
Defined in GHC.Tc.Types.Constraint Methods mempty :: RewriterSet Source # mappend :: RewriterSet -> RewriterSet -> RewriterSet Source # mconcat :: [RewriterSet] -> RewriterSet Source # | |
Semigroup RewriterSet Source # | |
Defined in GHC.Tc.Types.Constraint Methods (<>) :: RewriterSet -> RewriterSet -> RewriterSet Source # sconcat :: NonEmpty RewriterSet -> RewriterSet Source # stimes :: Integral b => b -> RewriterSet -> RewriterSet Source # | |
Outputable RewriterSet Source # | |
Defined in GHC.Tc.Types.Constraint Methods ppr :: RewriterSet -> SDoc Source # |
isEmptyRewriterSet :: RewriterSet -> Bool Source #
rewriterSetFromType :: Type -> RewriterSet Source #
Makes a RewriterSet
from all the coercion holes that occur in the
given type.
rewriterSetFromTypes :: [Type] -> RewriterSet Source #
Makes a RewriterSet
from all the coercion holes that occur in the
given types.
rewriterSetFromCo :: Coercion -> RewriterSet Source #
Makes a RewriterSet
from all the coercion holes that occur in the
given coercion.
addRewriterSet :: RewriterSet -> CoercionHole -> RewriterSet Source #
ctEvFlavour :: CtEvidence -> CtFlavour Source #
type CtFlavourRole = (CtFlavour, EqRel) Source #
Whether or not one Ct
can rewrite another is determined by its
flavour and its equality relation. See also
Note [Flavours with roles] in GHC.Tc.Solver.InertSet
ctEvFlavourRole :: CtEvidence -> CtFlavourRole Source #
Extract the flavour, role, and boxity from a CtEvidence
ctFlavourRole :: Ct -> CtFlavourRole Source #
Extract the flavour and role from a Ct
eqCanRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool Source #
pprEvVarTheta :: [EvVar] -> SDoc Source #
pprEvVarWithType :: EvVar -> SDoc Source #