ghc-9.4.3: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Tc.Utils.Instantiate

Synopsis

Documentation

newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence Source #

Create a new Wanted constraint with the given CtOrigin, and location information taken from the TcM environment.

newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence] Source #

Create new Wanted constraints with the given CtOrigin, and location information taken from the TcM environment.

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 :: SkolemInfo -> [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 newFamInst, and newClsInst

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

Give fresh uniques to a bunch of CoVars Used in "GHC.Tc.Instance.Family.newFamInst"

tcInstInvisibleTyBinders :: TcType -> TcKind -> TcM (TcType, TcKind) Source #

Given ty::forall k1 k2. k, instantiate all the invisible forall-binders returning ty kk1 kk2 :: k[kk1k1, kk2k1]

newMethodFromName Source #

Arguments

:: CtOrigin

why do we need this?

-> Name

name of the method

-> [TcRhoType]

types with which to instantiate the class

-> TcM (HsExpr GhcTc) 

Used when Name is the wired-in name for a wired-in class method, so the caller knows its type for sure, which should be of form

forall a. C a => <blah>

newMethodFromName is supposed to instantiate just the outer type variable and constraint

tcSyntaxName Source #

Arguments

:: CtOrigin 
-> TcType

Type to instantiate it at

-> (Name, HsExpr GhcRn)

(Standard name, user name)

-> TcM (Name, HsExpr GhcTc)

(Standard name, suitable expression) USED ONLY FOR CmdTop (sigh) *** See Note [CmdSyntaxTable] in GHC.Hs.Expr

tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet Source #

Returns free variables of WantedConstraints as a non-deterministic set. See Note [Deterministic FV] in GHC.Utils.FV.

tyCoVarsOfCt :: Ct -> TcTyCoVarSet Source #

Returns free variables of constraints as a non-deterministic set

tyCoVarsOfCts :: Cts -> TcTyCoVarSet Source #

Returns free variables of a bag of constraints as a non-deterministic set. See Note [Deterministic FV] in GHC.Utils.FV.