ghc-lib-parser-0.20220301: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Core.Predicate

Synopsis

Documentation

data Pred Source #

A predicate in the solver. The solver tries to prove Wanted predicates from Given ones.

Constructors

ClassPred Class [Type]

A typeclass predicate.

EqPred EqRel Type Type

A type equality predicate.

IrredPred PredType

An irreducible predicate.

ForAllPred [TyVar] [PredType] PredType

A quantified predicate.

See Note [Quantified constraints] in GHC.Tc.Solver.Canonical

SpecialPred SpecialPred Type

A special predicate, used internally in GHC.

The meaning of the type argument is dictated by the SpecialPred specified in the first agument; see the documentation of SpecialPred for more info.

Example: Concrete# rep, used for representation-polymorphism checks within GHC. See Note [The Concrete mechanism] in GHC.Tc.Utils.Concrete. (This is the only example currently. More to come: see GHC ticket #20000.)

data EqRel Source #

A choice of equality relation. This is separate from the type Role because Phantom does not define a (non-trivial) equality relation.

Constructors

NomEq 
ReprEq 

Instances

Instances details
Eq EqRel Source # 
Instance details

Defined in GHC.Core.Predicate

Methods

(==) :: EqRel -> EqRel -> Bool #

(/=) :: EqRel -> EqRel -> Bool #

Ord EqRel Source # 
Instance details

Defined in GHC.Core.Predicate

Methods

compare :: EqRel -> EqRel -> Ordering #

(<) :: EqRel -> EqRel -> Bool #

(<=) :: EqRel -> EqRel -> Bool #

(>) :: EqRel -> EqRel -> Bool #

(>=) :: EqRel -> EqRel -> Bool #

max :: EqRel -> EqRel -> EqRel #

min :: EqRel -> EqRel -> EqRel #

Outputable EqRel Source # 
Instance details

Defined in GHC.Core.Predicate

Methods

ppr :: EqRel -> SDoc Source #

predTypeEqRel :: PredType -> EqRel Source #

Get the equality relation relevant for a pred type.

mkPrimEqPred :: Type -> Type -> Type Source #

Creates a primitive type equality predicate. Invariant: the types are not Coercions

mkPrimEqPredRole :: Role -> Type -> Type -> PredType Source #

Makes a lifted equality predicate at the given role

mkHeteroPrimEqPred :: Kind -> Kind -> Type -> Type -> Type Source #

Creates a primitive type equality predicate with explicit kinds

mkHeteroReprPrimEqPred :: Kind -> Kind -> Type -> Type -> Type Source #

Creates a primitive representational type equality predicate with explicit kinds

data SpecialPred Source #

SpecialPred describes all the special predicates that are currently used in GHC.

These are different from the special typeclasses (such as KnownNat, Typeable, Coercible, ...), as special predicates can't be expressed as typeclasses, as they hold evidence of a different kind.

Constructors

ConcretePrimPred

A Concrete# predicate, to check for representation polymorphism.

When the first argument to the SpecialPred data constructor of Pred is ConcretePrimPred, the second argument is the type we are inspecting to decide whether it is concrete. That is, it refers to the second argument of the 'Concrete#' TyCon. Recall that this TyCon has kind

forall k. k -> TupleRep '[]

See Note [The Concrete mechanism] in GHC.Tc.Utils.Concrete for further details.

Instances

Instances details
Eq SpecialPred Source # 
Instance details

Defined in GHC.Core.Predicate

Outputable SpecialPred Source # 
Instance details

Defined in GHC.Core.Predicate

Methods

ppr :: SpecialPred -> SDoc Source #

specialPredTyCon :: SpecialPred -> TyCon Source #

Obtain the TyCon associated with a special predicate.

isCallStackTy :: Type -> Bool Source #

Is a type a CallStack?

isCallStackPred :: Class -> [Type] -> Maybe FastString Source #

Is a PredType a CallStack implicit parameter?

If so, return the name of the parameter.

isIPPred_maybe :: Type -> Maybe (FastString, Type) Source #

Decomposes a predicate if it is an implicit parameter. Does not look in superclasses. See also [Local implicit parameters].

type DictId = EvId Source #

Dictionary Identifier