Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- deeplySkolemise :: TcSigmaType -> TcM (HsWrapper, [(Name, 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 ()
- instTyVarsWith :: CtOrigin -> [TyVar] -> [TcType] -> TcM TCvSubst
- newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence
- newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence]
- tcInstInvisibleTyBinders :: Int -> TcKind -> TcM ([TcType], TcKind)
- tcInstInvisibleTyBinder :: TCvSubst -> TyBinder -> TcM (TCvSubst, TcType)
- newOverloadedLit :: HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId)
- mkOverLit :: OverLitVal -> TcM (HsLit GhcTc)
- 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 GhcTcId)
- tcSyntaxName :: CtOrigin -> TcType -> (Name, HsExpr GhcRn) -> TcM (Name, HsExpr GhcTcId)
- tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet
- tyCoVarsOfCt :: Ct -> TcTyCoVarSet
- tyCoVarsOfCts :: Cts -> TcTyCoVarSet
Documentation
deeplySkolemise :: TcSigmaType -> TcM (HsWrapper, [(Name, 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 Inferred
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 #
tcInstInvisibleTyBinders :: Int -> TcKind -> TcM ([TcType], TcKind) Source #
Instantiates up to n invisible binders Returns the instantiating types, and body kind
tcInstInvisibleTyBinder :: TCvSubst -> TyBinder -> TcM (TCvSubst, TcType) Source #
Used only in *types*
newOverloadedLit :: HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId) Source #
newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType -> Class -> [Type] -> TcM ClsInst Source #
tcGetInsts :: TcM [ClsInst] Source #
instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper Source #
:: CtOrigin | why do we need this? |
-> Name | name of the method |
-> [TcRhoType] | types with which to instantiate the class |
-> TcM (HsExpr GhcTcId) |
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 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 FV.