ghc-8.10.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

TcMType

Synopsis

Documentation

type TcTyVar = Var Source #

Type variable that might be a metavariable

newOpenFlexiTyVarTy :: TcM TcType Source #

Create a tyvar that can be a lifted or unlifted type. Returns alpha :: TYPE kappa, where both alpha and kappa are fresh

data ExpType Source #

An expected type to check against during type-checking. See Note [ExpType] in TcMType, where you'll also find manipulators.

Constructors

Check TcType 
Infer !InferResult 

Instances

Instances details
Outputable ExpType Source # 
Instance details

Defined in TcType

mkCheckExpType :: TcType -> ExpType Source #

Make an ExpType suitable for checking.

newInferExpTypeNoInst :: TcM ExpSigmaType Source #

Make an ExpType suitable for inferring a type of kind * or #.

readExpType :: ExpType -> TcM TcType Source #

Extract a type out of an ExpType. Otherwise, panics.

readExpType_maybe :: ExpType -> TcM (Maybe TcType) Source #

Extract a type out of an ExpType, if one exists. But one should always exist. Unless you're quite sure you know what you're doing.

expTypeToType :: ExpType -> TcM TcType Source #

Extracts the expected type if there is one, or generates a new TauTv if there isn't.

checkingExpType_maybe :: ExpType -> Maybe TcType Source #

Returns the expected type when in checking mode.

checkingExpType :: String -> ExpType -> TcType Source #

Returns the expected type when in checking mode. Panics if in inference mode.

tauifyExpType :: ExpType -> TcM ExpType Source #

Turn a (Infer hole) type into a (Check alpha), where alpha is a fresh unification variable

newHoleCt :: Hole -> Id -> Type -> TcM Ct Source #

Create a new CHoleCan Ct.

emitWanted :: CtOrigin -> TcPredType -> TcM EvTerm Source #

Emits a new Wanted. Deals with both equalities and non-equalities.

emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion Source #

Emits a new equality constraint

emitWantedEvVar :: CtOrigin -> TcPredType -> TcM EvVar Source #

Creates a new EvVar and immediately emits it as a Wanted. No equality predicates here.

newNoTcEvBinds :: TcM EvBindsVar Source #

Creates an EvBindsVar incapable of holding any bindings. It still tracks covar usages (see comments on ebv_tcvs in TcEvidence), thus must be made monadically

fillCoercionHole :: CoercionHole -> Coercion -> TcM () Source #

Put a value in a coercion hole

isFilledCoercionHole :: CoercionHole -> TcM Bool Source #

Is a coercion hole filled in?

unpackCoercionHole :: CoercionHole -> TcM Coercion Source #

Retrieve the contents of a coercion hole. Panics if the hole is unfilled

unpackCoercionHole_maybe :: CoercionHole -> TcM (Maybe Coercion) Source #

Retrieve the contents of a coercion hole, if it is filled

checkCoercionHole :: CoVar -> Coercion -> TcM Coercion Source #

Check that a coercion is appropriate for filling a hole. (The hole itself is needed only for printing. Always returns the checked coercion, but this return value is necessary so that the input coercion is forced only when the output is forced.

newImplication :: TcM Implication Source #

Create a new Implication with as many sensible defaults for its fields as possible. Note that the ic_tclvl, ic_binds, and ic_info fields do not have sensible defaults, so they are initialized with lazy thunks that will panic if forced, so one should take care to initialize these fields after creation.

This is monadic to look up the TcLclEnv, which is used to initialize ic_env, and to set the -Winaccessible-code flag. See Note [Avoid -Winaccessible-code when deriving] in TcInstDcls.

tcInstType Source #

Arguments

:: ([TyVar] -> TcM (TCvSubst, [TcTyVar]))

How to instantiate the type variables

-> Id

Type to instantiate

-> TcM ([(Name, TcTyVar)], TcThetaType, TcType)

Result (type vars, preds (incl equalities), rho)

tcInstSkolTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar]) Source #

Given a list of [TyVar], skolemize the type variables, returning a substitution mapping the original tyvars to the skolems, and the list of newly bound skolems.

freshenTyVarBndrs :: [TyVar] -> TcM (TCvSubst, [TyVar]) Source #

Give fresh uniques to a bunch of TyVars, but they stay as TyVars, rather than becoming TcTyVars Used in FamInst.newFamInst, and Inst.newClsInst

freshenCoVarBndrsX :: TCvSubst -> [CoVar] -> TcM (TCvSubst, [CoVar]) Source #

Give fresh uniques to a bunch of CoVars Used in FamInst.newFamInst

candidateQTyVarsOfType :: TcType -> TcM CandidatesQTvs Source #

Gathers free variables to use as quantification candidates (in quantifyTyVars). This might output the same var in both sets, if it's used in both a type and a kind. The variables to quantify must have a TcLevel strictly greater than the ambient level. (See Wrinkle in Note [Naughty quantification candidates]) See Note [CandidatesQTvs determinism and order] See Note [Dependent type variables]

candidateQTyVarsOfKind :: TcKind -> TcM CandidatesQTvs Source #

Like candidateQTyVarsOfType, but consider every free variable to be dependent. This is appropriate when generalizing a *kind*, instead of a type. (That way, -XNoPolyKinds will default the variables to Type.)

candidateQTyVarsOfTypes :: [Type] -> TcM CandidatesQTvs Source #

Like candidateQTyVarsOfType, but over a list of types The variables to quantify must have a TcLevel strictly greater than the ambient level. (See Wrinkle in Note [Naughty quantification candidates])

zonkCo :: Coercion -> TcM Coercion Source #

Zonk a coercion -- really, just zonk any types in the coercion

ensureNotLevPoly :: Type -> SDoc -> TcM () Source #

According to the rules around representation polymorphism (see https://gitlab.haskell.org/ghc/ghc/wikis/no-sub-kinds), no binder can have a representation-polymorphic type. This check ensures that we respect this rule. It is a bit regrettable that this error occurs in zonking, after which we should have reported all errors. But it's hard to see where else to do it, because this can be discovered only after all solving is done. And, perhaps most importantly, this isn't really a compositional property of a type system, so it's not a terrible surprise that the check has to go in an awkward spot.

checkForLevPolyX :: Monad m => (SDoc -> m ()) -> SDoc -> Type -> m () Source #