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

GHC.Tc.Gen.HsType

Description

Typechecking user-specified MonoTypes

Synopsis

Documentation

kcClassSigType :: SkolemInfo -> [Located Name] -> LHsSigType GhcRn -> TcM () Source #

tcClassSigType :: SkolemInfo -> [Located Name] -> LHsSigType GhcRn -> TcM Type Source #

tcHsSigType :: UserTypeCtxt -> LHsSigType GhcRn -> TcM Type Source #

tcHsSigWcType :: UserTypeCtxt -> LHsSigWcType GhcRn -> TcM Type Source #

tcHsPartialSigType :: UserTypeCtxt -> LHsSigWcType GhcRn -> TcM ([(Name, TcTyVar)], Maybe TcType, [(Name, InvisTVBinder)], TcThetaType, TcType) Source #

tcStandaloneKindSig :: LStandaloneKindSig GhcRn -> TcM (Name, Kind) Source #

addSigCtxt :: UserTypeCtxt -> LHsType GhcRn -> TcM a -> TcM a Source #

pprSigCtxt :: UserTypeCtxt -> LHsType GhcRn -> SDoc Source #

tcHsClsInstType :: UserTypeCtxt -> LHsSigType GhcRn -> TcM Type Source #

tcHsDeriv :: LHsSigType GhcRn -> TcM ([TyVar], Class, [Type], [Kind]) Source #

tcDerivStrategy Source #

Arguments

:: Maybe (LDerivStrategy GhcRn)

The deriving strategy

-> TcM (Maybe (LDerivStrategy GhcTc), [TyVar])

The typechecked deriving strategy and the tyvars that it binds (if using ViaStrategy).

Typecheck a deriving strategy. For most deriving strategies, this is a no-op, but for the via strategy, this requires typechecking the via type.

tcHsTypeApp :: LHsWcType GhcRn -> Kind -> TcM Type Source #

Type-check a visible type application

bindImplicitTKBndrs_Tv :: [Name] -> TcM a -> TcM ([TcTyVar], a) Source #

bindImplicitTKBndrs_Skol :: [Name] -> TcM a -> TcM ([TcTyVar], a) Source #

bindImplicitTKBndrs_Q_Tv :: [Name] -> TcM a -> TcM ([TcTyVar], a) Source #

bindImplicitTKBndrs_Q_Skol :: [Name] -> TcM a -> TcM ([TcTyVar], a) Source #

bindExplicitTKBndrs_Tv :: OutputableBndrFlag flag => [LHsTyVarBndr flag GhcRn] -> TcM a -> TcM ([VarBndr TyVar flag], a) Source #

bindExplicitTKBndrs_Skol :: OutputableBndrFlag flag => [LHsTyVarBndr flag GhcRn] -> TcM a -> TcM ([VarBndr TyVar flag], a) Source #

bindExplicitTKBndrs_Q_Tv :: ContextKind -> [LHsTyVarBndr () GhcRn] -> TcM a -> TcM ([TcTyVar], a) Source #

bindExplicitTKBndrs_Q_Skol :: ContextKind -> [LHsTyVarBndr () GhcRn] -> TcM a -> TcM ([TcTyVar], a) Source #

data ContextKind Source #

Describes the kind expected in a certain context.

Constructors

TheKind Kind

a specific kind

AnyKind

any kind will do

OpenKind

something of the form TYPE _

bindTyClTyVars :: Name -> (TcTyCon -> [TyConBinder] -> Kind -> TcM a) -> TcM a Source #

Used for the type variables of a type or class decl in the "kind checking" and "type checking" pass, but not in the initial-kind run.

tcFamTyPats :: TyCon -> HsTyPats GhcRn -> TcM (TcType, TcKind) Source #

etaExpandAlgTyCon :: [TyConBinder] -> Kind -> TcM ([TyConBinder], Kind) Source #

tcbVisibilities :: TyCon -> [Type] -> [TyConBndrVis] Source #

data SAKS_or_CUSK Source #

Constructors

SAKS Kind 
CUSK 

Instances

Instances details
Outputable SAKS_or_CUSK Source # 
Instance details

Defined in GHC.Tc.Gen.HsType

Methods

ppr :: SAKS_or_CUSK -> SDoc

pprPrec :: Rational -> SAKS_or_CUSK -> SDoc

kcDeclHeader Source #

Arguments

:: InitialKindStrategy 
-> Name

of the thing being checked

-> TyConFlavour

What sort of TyCon is being checked

-> LHsQTyVars GhcRn

Binders in the header

-> TcM ContextKind

The result kind

-> TcM TcTyCon

A suitably-kinded TcTyCon

tcNamedWildCardBinders :: [Name] -> ([(Name, TcTyVar)] -> TcM a) -> TcM a Source #

tcHsLiftedType :: LHsType GhcRn -> TcM TcType Source #

tcHsOpenType :: LHsType GhcRn -> TcM TcType Source #

tcHsLiftedTypeNC :: LHsType GhcRn -> TcM TcType Source #

tcHsOpenTypeNC :: LHsType GhcRn -> TcM TcType Source #

tcInferLHsTypeKind :: LHsType GhcRn -> TcM (TcType, TcKind) Source #

tcInferLHsType :: LHsType GhcRn -> TcM TcType Source #

tcInferLHsTypeUnsaturated :: LHsType GhcRn -> TcM (TcType, TcKind) Source #

tcCheckLHsType :: LHsType GhcRn -> ContextKind -> TcM TcType Source #

tcHsMbContext :: Maybe (LHsContext GhcRn) -> TcM [PredType] Source #

tcHsContext :: LHsContext GhcRn -> TcM [PredType] Source #

tcLHsPredType :: LHsType GhcRn -> TcM PredType Source #

failIfEmitsConstraints :: TcM a -> TcM a Source #

If the inner action emits constraints, report them as errors and fail; otherwise, propagates the return value. Useful as a wrapper around tcImplicitTKBndrs, which uses solveLocalEqualities, when there won't be another chance to solve constraints

solveEqualities :: TcM a -> TcM a Source #

Type-check a thing that emits only equality constraints, then solve those constraints. Fails outright if there is trouble. Use this if you're not going to get another crack at solving (because, e.g., you're checking a datatype declaration)

kindGeneralizeAll :: TcType -> TcM [KindVar] Source #

Specialized version of kindGeneralizeSome, but where all variables can be generalized. Use this variant when you can be sure that no more constraints on the type's metavariables will arise or be solved.

kindGeneralizeSome Source #

Arguments

:: (TcTyVar -> Bool) 
-> TcType

needn't be zonked

-> TcM [KindVar] 

Generalize some of the free variables in the given type. All such variables should be *kind* variables; any type variables should be explicitly quantified (with a forall) before now. The supplied predicate says which free variables to quantify. But in all cases, generalize only those variables whose TcLevel is strictly greater than the ambient level. This "strictly greater than" means that you likely need to push the level before creating whatever type gets passed here. Any variable whose level is greater than the ambient level but is not selected to be generalized will be promoted. (See [Promoting unification variables] in GHC.Tc.Solver and Note [Recipe for checking a signature].) The resulting KindVar are the variables to quantify over, in the correct, well-scoped order. They should generally be Inferred, not Specified, but that's really up to the caller of this function.

kindGeneralizeNone :: TcType -> TcM () Source #

Specialized version of kindGeneralizeSome, but where no variables can be generalized, but perhaps some may neeed to be promoted. Use this variant when it is unknowable whether metavariables might later be constrained.

To see why this promotion is needed, see Note [Recipe for checking a signature], and especially Note [Promotion in signatures].

tcLHsKindSig :: UserTypeCtxt -> LHsKind GhcRn -> TcM Kind Source #

checkDataKindSig :: DataSort -> Kind -> TcM () Source #

Checks that the return kind in a data declaration's kind signature is permissible. There are three cases:

If dealing with a data, newtype, data instance, or newtype instance declaration, check that the return kind is Type.

If the declaration is a newtype or newtype instance and the UnliftedNewtypes extension is enabled, this check is slightly relaxed so that a return kind of the form TYPE r (for some r) is permitted. See Note [Implementation of UnliftedNewtypes] in GHC.Tc.TyCl.

If dealing with a data family declaration, check that the return kind is either of the form:

  1. TYPE r (for some r), or
  2. k (where k is a bare kind variable; see #12369)

See also Note [Datatype return kinds] in GHC.Tc.TyCl

data DataSort Source #

A description of whether something is a

At present, this data type is only consumed by checkDataKindSig.

Constructors

DataDeclSort NewOrData 
DataInstanceSort NewOrData 
DataFamilySort 

checkClassKindSig :: Kind -> TcM () Source #

Checks that the result kind of a class is exactly Constraint, rejecting type synonyms and type families that reduce to Constraint. See #16826.

tcMult :: HsArrow GhcRn -> TcM Mult Source #

tcHsPatSigType :: UserTypeCtxt -> HsPatSigType GhcRn -> TcM ([(Name, TcTyVar)], [(Name, TcTyVar)], TcType) Source #

funAppCtxt :: (Outputable fun, Outputable arg) => fun -> arg -> Int -> SDoc Source #

Make an appropriate message for an error in a function argument. Used for both expressions and types.

addTyConFlavCtxt :: Name -> TyConFlavour -> TcM a -> TcM a Source #

Add a "In the data declaration for T" or some such.