| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Tc.Utils.Instantiate
Synopsis
- topSkolemise :: SkolemInfo -> TcSigmaType -> TcM (HsWrapper, [(Name, TyVar)], [EvVar], TcRhoType)
 - topInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
 - instantiateSigma :: CtOrigin -> [TyVar] -> TcThetaType -> TcSigmaType -> TcM ([TcTyVar], HsWrapper, TcSigmaType)
 - instCall :: CtOrigin -> [TcType] -> TcThetaType -> TcM HsWrapper
 - instDFunType :: DFunId -> [DFunInstType] -> TcM ([TcType], TcThetaType)
 - instStupidTheta :: CtOrigin -> TcThetaType -> TcM ()
 - instTyVarsWith :: CtOrigin -> [TyVar] -> [TcType] -> TcM Subst
 - newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence
 - newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence]
 - tcInstType :: ([TyVar] -> TcM (Subst, [TcTyVar])) -> Id -> TcM ([(Name, TcTyVar)], TcThetaType, TcType)
 - tcInstTypeBndrs :: Type -> TcM ([(Name, InvisTVBinder)], TcThetaType, TcType)
 - tcSkolemiseInvisibleBndrs :: SkolemInfoAnon -> Type -> TcM ([TcTyVar], TcType)
 - tcInstSkolTyVars :: SkolemInfo -> [TyVar] -> TcM (Subst, [TcTyVar])
 - tcInstSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcM (Subst, [TcTyVar])
 - tcSkolDFunType :: Type -> TcM (SkolemInfoAnon, [TcTyVar], TcThetaType, Class, [TcType])
 - tcSuperSkolTyVars :: TcLevel -> SkolemInfo -> [TyVar] -> (Subst, [TcTyVar])
 - tcInstSuperSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcM (Subst, [TcTyVar])
 - freshenTyVarBndrs :: [TyVar] -> TcM (Subst, [TyVar])
 - freshenCoVarBndrsX :: Subst -> [CoVar] -> TcM (Subst, [CoVar])
 - tcInstInvisibleTyBindersN :: Int -> TcKind -> TcM ([TcType], TcKind)
 - tcInstInvisibleTyBinders :: TcType -> TcKind -> TcM (TcType, TcKind)
 - tcInstInvisibleTyBinder :: Subst -> TyVar -> TcM (Subst, TcType)
 - newOverloadedLit :: HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTc)
 - mkOverLit :: OverLitVal -> TcM (HsLit GhcTc)
 - newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType -> Class -> [Type] -> TcM ClsInst
 - newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcM FamInst
 - tcGetInsts :: TcM [ClsInst]
 - tcGetInstEnvs :: TcM InstEnvs
 - getOverlapFlag :: Maybe OverlapMode -> TcM OverlapFlag
 - tcExtendLocalInstEnv :: [ClsInst] -> TcM a -> TcM a
 - instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper
 - newMethodFromName :: CtOrigin -> Name -> [TcRhoType] -> TcM (HsExpr GhcTc)
 - tcSyntaxName :: CtOrigin -> TcType -> (Name, HsExpr GhcRn) -> TcM (Name, HsExpr GhcTc)
 - tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet
 - tyCoVarsOfCt :: Ct -> TcTyCoVarSet
 - tyCoVarsOfCts :: Cts -> TcTyCoVarSet
 
Documentation
topSkolemise :: SkolemInfo -> TcSigmaType -> TcM (HsWrapper, [(Name, TyVar)], [EvVar], TcRhoType) Source #
topInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType) Source #
instantiateSigma :: CtOrigin -> [TyVar] -> TcThetaType -> TcSigmaType -> TcM ([TcTyVar], HsWrapper, TcSigmaType) Source #
instDFunType :: DFunId -> [DFunInstType] -> TcM ([TcType], TcThetaType) Source #
instStupidTheta :: CtOrigin -> TcThetaType -> TcM () Source #
newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence Source #
newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence] Source #
tcInstTypeBndrs :: Type -> TcM ([(Name, InvisTVBinder)], TcThetaType, TcType) Source #
tcSkolemiseInvisibleBndrs :: SkolemInfoAnon -> Type -> TcM ([TcTyVar], TcType) Source #
tcInstSkolTyVars :: SkolemInfo -> [TyVar] -> TcM (Subst, [TcTyVar]) Source #
Given a list of [, skolemize the type variables,
 returning a substitution mapping the original tyvars to the
 skolems, and the list of newly bound skolems.TyVar]
tcInstSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcM (Subst, [TcTyVar]) Source #
tcSkolDFunType :: Type -> TcM (SkolemInfoAnon, [TcTyVar], TcThetaType, Class, [TcType]) Source #
tcSuperSkolTyVars :: TcLevel -> SkolemInfo -> [TyVar] -> (Subst, [TcTyVar]) Source #
tcInstSuperSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcM (Subst, [TcTyVar]) Source #
freshenTyVarBndrs :: [TyVar] -> TcM (Subst, [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 :: Subst -> [CoVar] -> TcM (Subst, [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]
 Called only to instantiate kinds, in user-written type signatures
newOverloadedLit :: HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTc) Source #
newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType -> Class -> [Type] -> TcM ClsInst Source #
newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcM FamInst Source #
tcGetInsts :: TcM [ClsInst] Source #
instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper 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
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.