ghc-lib-parser-0.20191201: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

Constraint

Synopsis

Documentation

data QCInst Source #

Constructors

QCI 
Instances
Outputable QCInst Source # 
Instance details

Defined in Constraint

type Xi = Type Source #

type Cts = Bag Ct 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]

getUserTypeErrorMsg :: Ct -> 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]

ctFlavour :: Ct -> CtFlavour Source #

Get the flavour of the given Ct

ctEqRel :: Ct -> EqRel Source #

Get the equality relation for the given Ct

mkTcEqPredLikeEv :: CtEvidence -> TcType -> TcType -> TcType Source #

Makes a new equality predicate with the same role as the given evidence.

mkGivens :: CtLoc -> [EvId] -> [Ct] Source #

ctEvEqRel :: CtEvidence -> EqRel Source #

Get the equality relation relevant for a CtEvidence

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

tyCoVarsOfCtList :: Ct -> [TcTyCoVar] Source #

Returns free variables of constraints as a deterministically ordered. list. See Note [Deterministic FV] in FV.

tyCoVarsOfCtsList :: Cts -> [TcTyCoVar] Source #

Returns free variables of a bag of constraints as a deterministically odered list. See Note [Deterministic FV] in FV.

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.

tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet Source #

Returns free variables of WantedConstraints as a non-deterministic set. See Note [Deterministic FV] in FV.

tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] Source #

Returns free variables of WantedConstraints as a deterministically ordered list. See Note [Deterministic FV] in FV.

data TcEvDest Source #

A place for type-checking evidence to go after it is generated. Wanted equalities are always HoleDest; other wanteds are always 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 TyCoRep

Instances
Outputable TcEvDest Source # 
Instance details

Defined in Constraint

toKindLoc :: CtLoc -> CtLoc Source #

Take a CtLoc and moves it to the kind level

ctEvRole :: CtEvidence -> Role Source #

Get the role relevant for a CtEvidence

wrapTypeWithImplication :: Type -> Implication -> Type Source #

Wraps the given type with the constraints (via ic_given) in the given implication, according to the variables mentioned (via ic_skols) in the implication, but taking care to only wrap those variables that are mentioned in the type or the implication.

data CtFlavour Source #

Constructors

Given 
Wanted ShadowInfo 
Derived 
Instances
Eq CtFlavour Source # 
Instance details

Defined in Constraint

Outputable CtFlavour Source # 
Instance details

Defined in Constraint

data ShadowInfo Source #

Constructors

WDeriv 
WOnly 
Instances
Eq ShadowInfo Source # 
Instance details

Defined in Constraint

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 TcSMonad

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

data HoleSort Source #

Used to indicate which sort of hole we have.

Constructors

ExprHole

Either an out-of-scope variable or a "true" hole in an expression (TypedHoles)

TypeHole

A hole in a type (PartialTypeSignatures)