Safe Haskell | None |
---|---|
Language | Haskell2010 |
- deeplySkolemise :: TcSigmaType -> TcM (HsWrapper, [TyVar], [EvVar], TcRhoType)
- topInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
- topInstantiateInferred :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcSigmaType)
- deeplyInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
- instCall :: CtOrigin -> [TcType] -> TcThetaType -> TcM HsWrapper
- instDFunType :: DFunId -> [DFunInstType] -> TcM ([TcType], TcThetaType)
- instStupidTheta :: CtOrigin -> TcThetaType -> TcM ()
- newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence
- newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence]
- tcInstBinders :: [TyBinder] -> TcM (TCvSubst, [TcType])
- tcInstBindersX :: TCvSubst -> Maybe (VarEnv Kind) -> [TyBinder] -> TcM (TCvSubst, [TcType])
- newOverloadedLit :: HsOverLit Name -> ExpRhoType -> TcM (HsOverLit TcId)
- mkOverLit :: OverLitVal -> TcM HsLit
- newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType -> Class -> [Type] -> TcM ClsInst
- 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 TcId)
- tcSyntaxName :: CtOrigin -> TcType -> (Name, HsExpr Name) -> TcM (Name, HsExpr TcId)
- tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet
- tyCoVarsOfCt :: Ct -> TcTyCoVarSet
- tyCoVarsOfCts :: Cts -> TcTyCoVarSet
Documentation
deeplySkolemise :: TcSigmaType -> TcM (HsWrapper, [TyVar], [EvVar], TcRhoType) Source #
topInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType) Source #
Instantiate all outer type variables and any context. Never looks through arrows.
topInstantiateInferred :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcSigmaType) Source #
Instantiate all outer Invisible
binders
and any context. Never looks through arrows or specified type variables.
Used for visible type application.
deeplyInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType) 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 #
tcInstBinders :: [TyBinder] -> TcM (TCvSubst, [TcType]) Source #
This is used to instantiate binders when type-checking *types* only. See also Note [Bidirectional type checking]
tcInstBindersX :: TCvSubst -> Maybe (VarEnv Kind) -> [TyBinder] -> TcM (TCvSubst, [TcType]) Source #
This is used to instantiate binders when type-checking *types* only.
The VarEnv Kind
gives some known instantiations.
See also Note [Bidirectional type checking]
newOverloadedLit :: HsOverLit Name -> ExpRhoType -> TcM (HsOverLit TcId) Source #
newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType -> Class -> [Type] -> TcM ClsInst Source #
tcGetInsts :: TcM [ClsInst] Source #
instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper Source #
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 FV.