Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Type subsumption and unification
Synopsis
- tcWrapResult :: HsExpr GhcRn -> HsExpr GhcTc -> TcSigmaType -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcWrapResultO :: CtOrigin -> HsExpr GhcRn -> HsExpr GhcTc -> TcSigmaType -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcWrapResultMono :: HsExpr GhcRn -> HsExpr GhcTc -> TcRhoType -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcSkolemise :: UserTypeCtxt -> TcSigmaType -> (TcType -> TcM result) -> TcM (HsWrapper, result)
- tcSkolemiseScoped :: UserTypeCtxt -> TcSigmaType -> (TcType -> TcM result) -> TcM (HsWrapper, result)
- tcSkolemiseET :: UserTypeCtxt -> ExpSigmaType -> (ExpRhoType -> TcM result) -> TcM (HsWrapper, result)
- tcSubType :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> ExpRhoType -> TcM HsWrapper
- tcSubTypeSigma :: UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper
- tcSubTypePat :: CtOrigin -> UserTypeCtxt -> ExpSigmaType -> TcSigmaType -> TcM HsWrapper
- tcSubMult :: CtOrigin -> Mult -> Mult -> TcM HsWrapper
- checkConstraints :: SkolemInfo -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result)
- checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result
- buildImplicationFor :: TcLevel -> SkolemInfo -> [TcTyVar] -> [EvVar] -> WantedConstraints -> TcM (Bag Implication, TcEvBinds)
- buildTvImplication :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM Implication
- emitResidualTvConstraint :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM ()
- unifyType :: Maybe SDoc -> TcTauType -> TcTauType -> TcM TcCoercionN
- unifyKind :: Maybe SDoc -> TcKind -> TcKind -> TcM CoercionN
- unifyExpectedType :: HsExpr GhcRn -> TcRhoType -> ExpRhoType -> TcM TcCoercionN
- uType :: TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM CoercionN
- promoteTcType :: TcLevel -> TcType -> TcM (TcCoercionN, TcType)
- swapOverTyVars :: Bool -> TcTyVar -> TcTyVar -> Bool
- canSolveByUnification :: MetaInfo -> TcType -> Bool
- tcInfer :: (ExpSigmaType -> TcM a) -> TcM (a, TcSigmaType)
- matchExpectedListTy :: TcRhoType -> TcM (TcCoercionN, TcRhoType)
- matchExpectedTyConApp :: TyCon -> TcRhoType -> TcM (TcCoercionN, [TcSigmaType])
- matchExpectedAppTy :: TcRhoType -> TcM (TcCoercion, (TcSigmaType, TcSigmaType))
- matchExpectedFunTys :: forall a. SDoc -> UserTypeCtxt -> Arity -> ExpRhoType -> ([Scaled ExpSigmaType] -> ExpRhoType -> TcM a) -> TcM (HsWrapper, a)
- matchExpectedFunKind :: Outputable fun => fun -> Arity -> TcKind -> TcM Coercion
- matchActualFunTySigma :: SDoc -> Maybe SDoc -> (Arity, [Scaled TcSigmaType]) -> TcRhoType -> TcM (HsWrapper, Scaled TcSigmaType, TcSigmaType)
- matchActualFunTysRho :: SDoc -> CtOrigin -> Maybe SDoc -> Arity -> TcSigmaType -> TcM (HsWrapper, [Scaled TcSigmaType], TcRhoType)
- checkTyVarEq :: DynFlags -> TcTyVar -> TcType -> CheckTyEqResult
- checkTyFamEq :: DynFlags -> TyCon -> [TcType] -> TcType -> CheckTyEqResult
- checkTypeEq :: DynFlags -> CanEqLHS -> TcType -> CheckTyEqResult
Documentation
tcWrapResult :: HsExpr GhcRn -> HsExpr GhcTc -> TcSigmaType -> ExpRhoType -> TcM (HsExpr GhcTc) Source #
tcWrapResultO :: CtOrigin -> HsExpr GhcRn -> HsExpr GhcTc -> TcSigmaType -> ExpRhoType -> TcM (HsExpr GhcTc) Source #
tcWrapResultMono :: HsExpr GhcRn -> HsExpr GhcTc -> TcRhoType -> ExpRhoType -> TcM (HsExpr GhcTc) Source #
:: UserTypeCtxt | |
-> TcSigmaType | |
-> (TcType -> TcM result) | |
-> TcM (HsWrapper, result) | The wrapper has type: spec_ty ~> expected_ty See Note [Skolemisation] for the differences between tcSkolemiseScoped and tcSkolemise |
:: UserTypeCtxt | |
-> TcSigmaType | |
-> (TcType -> TcM result) | |
-> TcM (HsWrapper, result) | The wrapper has type: spec_ty ~> expected_ty See Note [Skolemisation] for the differences between tcSkolemiseScoped and tcSkolemise |
tcSkolemiseET :: UserTypeCtxt -> ExpSigmaType -> (ExpRhoType -> TcM result) -> TcM (HsWrapper, result) Source #
Variant of tcSkolemise
that takes an ExpType
tcSubType :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> ExpRhoType -> TcM HsWrapper Source #
tcSubTypeSigma :: UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper Source #
tcSubTypePat :: CtOrigin -> UserTypeCtxt -> ExpSigmaType -> TcSigmaType -> TcM HsWrapper Source #
checkConstraints :: SkolemInfo -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result) Source #
checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result Source #
buildImplicationFor :: TcLevel -> SkolemInfo -> [TcTyVar] -> [EvVar] -> WantedConstraints -> TcM (Bag Implication, TcEvBinds) Source #
buildTvImplication :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM Implication Source #
emitResidualTvConstraint :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM () Source #
unifyExpectedType :: HsExpr GhcRn -> TcRhoType -> ExpRhoType -> TcM TcCoercionN Source #
promoteTcType :: TcLevel -> TcType -> TcM (TcCoercionN, TcType) Source #
tcInfer :: (ExpSigmaType -> TcM a) -> TcM (a, TcSigmaType) Source #
Infer a type using a fresh ExpType See also Note [ExpType] in GHC.Tc.Utils.TcMType
matchExpectedListTy :: TcRhoType -> TcM (TcCoercionN, TcRhoType) Source #
matchExpectedTyConApp :: TyCon -> TcRhoType -> TcM (TcCoercionN, [TcSigmaType]) Source #
matchExpectedAppTy :: TcRhoType -> TcM (TcCoercion, (TcSigmaType, TcSigmaType)) Source #
matchExpectedFunTys :: forall a. SDoc -> UserTypeCtxt -> Arity -> ExpRhoType -> ([Scaled ExpSigmaType] -> ExpRhoType -> TcM a) -> TcM (HsWrapper, a) Source #
:: Outputable fun | |
=> fun | type, only for errors |
-> Arity | n: number of desired arrows |
-> TcKind | fun_ kind |
-> TcM Coercion | co :: fun_kind ~ (arg1 -> ... -> argn -> res) |
Breaks apart a function kind into its pieces.
matchActualFunTySigma :: SDoc -> Maybe SDoc -> (Arity, [Scaled TcSigmaType]) -> TcRhoType -> TcM (HsWrapper, Scaled TcSigmaType, TcSigmaType) Source #
matchActualFunTySigma does looks for just one function arrow returning an uninstantiated sigma-type
matchActualFunTysRho :: SDoc -> CtOrigin -> Maybe SDoc -> Arity -> TcSigmaType -> TcM (HsWrapper, [Scaled TcSigmaType], TcRhoType) Source #
checkTyVarEq :: DynFlags -> TcTyVar -> TcType -> CheckTyEqResult Source #
checkTyFamEq :: DynFlags -> TyCon -> [TcType] -> TcType -> CheckTyEqResult Source #
checkTypeEq :: DynFlags -> CanEqLHS -> TcType -> CheckTyEqResult Source #