ghc-9.15: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Core.TyCo.Compare

Description

Type equality and comparison

Synopsis

Type equality

eqType :: HasCallStack => Type -> Type -> Bool Source #

Type equality comparing both visible and invisible arguments, expanding synonyms and respecting multiplicities.

eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool Source #

Compare types with respect to a (presumably) non-empty RnEnv2.

eqTypes :: [Type] -> [Type] -> Bool Source #

Type equality on lists of types, looking through type synonyms

pickyEqType :: Type -> Type -> Bool Source #

Like pickyEqTypeVis, but returns a Bool for convenience

tcEqTypeNoKindCheck :: Type -> Type -> Bool Source #

Just like tcEqType, but will return True for types of different kinds as long as their non-coercion structure is identical.

tcEqTyConApps :: TyCon -> [Type] -> TyCon -> [Type] -> Bool Source #

Check whether two TyConApps are the same; if the number of arguments are different, just checks the common prefix of arguments.

Dealing with invisible bits in types

mayLookIdentical :: Type -> Type -> InvisibleBits Source #

mayLookIdentical returns:

  • An empty set if the two types are distinct unequal, and remain distinct even if we hide explicit kinds, runtime-reps, multiplicities.
  • A non-empty set of invis_bits, if the two types might look equal, but are in fact distinct in the returned invis_bits.

See Note [mayLookIdentical], as well as Note [Showing invisible bits of types in error messages] in GHC.Tc.Errors.Ppr.

pprWithInvisibleBits :: Set InvisibleBit -> SDoc -> SDoc Source #

Make the sure the given invisible bits are displayed.

See Note [Showing invisible bits of types in error messages] in GHC.Tc.Errors.Ppr.

data InvisibleBit Source #

Something in a type which might be invisible.

Used to avoid reporting confusing errors to the user, like:

Couldn't match (a -> b) with (a -> b)

When in fact it is e.g. (a %1 -> b) vs (a %Many -> b), but the multiplicites have been suppressed.

See Note [Showing invisible bits of types in error messages] in GHC.Tc.Errors.Ppr.

Type comparison

Visiblity comparision

eqForAllVis :: ForAllTyFlag -> ForAllTyFlag -> Bool Source #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.

cmpForAllVis :: ForAllTyFlag -> ForAllTyFlag -> Ordering Source #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.