ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Core.Class

Synopsis

Documentation

data Class Source #

Instances

Instances details
Data Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class Source #

toConstr :: Class -> Constr Source #

dataTypeOf :: Class -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) Source #

gmapT :: (forall b. Data b => b -> b) -> Class -> Class Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source #

NamedThing Class Source # 
Instance details

Defined in GHC.Core.Class

Uniquable Class Source # 
Instance details

Defined in GHC.Core.Class

Outputable Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc Source #

Eq Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

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

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

data ClassATItem Source #

Constructors

ATI TyCon (Maybe (Type, TyFamEqnValidityInfo))

Default associated type (if any) from this template.

As per Note [Associated type defaults], the Type has been renamed to use the class tyvars, while the TyFamEqnValidityInfo uses the original user-written type variables.

data TyFamEqnValidityInfo Source #

Information about a type family equation, used for validity checking of closed type family equations and associated type family default equations.

This type exists to delay validity-checking after typechecking type declaration groups, to avoid cyclic evaluation inside the typechecking knot.

See Note [Type-checking default assoc decls] in GHC.Tc.TyCl.

Constructors

NoVI

Used for equations which don't need any validity checking, for example equations imported from another module.

VI

Information necessary for validity checking of a type family equation.

Fields

  • vi_loc :: SrcSpan
     
  • vi_qtvs :: [TcTyVar]

    LHS quantified type variables

  • vi_non_user_tvs :: TyVarSet

    non-user-written type variables (for error message reporting)

    Example: with -XPolyKinds, typechecking type instance forall a. F = () introduces the kind variable k for the kind of a. See #23734.

  • vi_pats :: [Type]

    LHS patterns

  • vi_rhs :: Type

    RHS of the equation

    NB: for associated type family default declarations, this is the RHS *before* applying the substitution from Note [Type-checking default assoc decls] in GHC.Tc.TyCl.

type FunDep a = ([a], [a]) Source #