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)
- tcTopSkolemise :: UserTypeCtxt -> TcSigmaType -> (TcType -> TcM result) -> TcM (HsWrapper, result)
- tcSkolemiseScoped :: UserTypeCtxt -> TcSigmaType -> (TcType -> TcM result) -> TcM (HsWrapper, result)
- tcSkolemiseExpType :: UserTypeCtxt -> ExpSigmaType -> (ExpRhoType -> TcM result) -> TcM (HsWrapper, result)
- tcSubType :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> ExpRhoType -> TcM HsWrapper
- tcSubTypeSigma :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper
- tcSubTypePat :: CtOrigin -> UserTypeCtxt -> ExpSigmaType -> TcSigmaType -> TcM HsWrapper
- tcSubTypeDS :: HsExpr GhcRn -> TcRhoType -> ExpRhoType -> TcM HsWrapper
- tcSubTypeAmbiguity :: UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper
- tcSubMult :: CtOrigin -> Mult -> Mult -> TcM HsWrapper
- checkConstraints :: SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result)
- checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result
- buildImplicationFor :: TcLevel -> SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> WantedConstraints -> TcM (Bag Implication, TcEvBinds)
- buildTvImplication :: SkolemInfoAnon -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM Implication
- emitResidualTvConstraint :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM ()
- unifyType :: Maybe TypedThing -> TcTauType -> TcTauType -> TcM TcCoercionN
- unifyKind :: Maybe TypedThing -> 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
- startSolvingByUnification :: MetaInfo -> TcType -> TcM (Maybe TcType)
- 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. ExpectedFunTyOrigin -> UserTypeCtxt -> Arity -> ExpRhoType -> ([Scaled ExpSigmaTypeFRR] -> ExpRhoType -> TcM a) -> TcM (HsWrapper, a)
- matchExpectedFunKind :: TypedThing -> Arity -> TcKind -> TcM Coercion
- matchActualFunTySigma :: ExpectedFunTyOrigin -> Maybe TypedThing -> (Arity, [Scaled TcSigmaType]) -> TcRhoType -> TcM (HsWrapper, Scaled TcSigmaTypeFRR, TcSigmaType)
- matchActualFunTysRho :: ExpectedFunTyOrigin -> CtOrigin -> Maybe TypedThing -> Arity -> TcSigmaType -> TcM (HsWrapper, [Scaled TcSigmaTypeFRR], TcRhoType)
- checkTyVarEq :: TcTyVar -> TcType -> CheckTyEqResult
- checkTyFamEq :: TyCon -> [TcType] -> TcType -> CheckTyEqResult
- checkTypeEq :: 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 tcTopSkolemise |
:: 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 tcTopSkolemise |
tcSkolemiseExpType :: UserTypeCtxt -> ExpSigmaType -> (ExpRhoType -> TcM result) -> TcM (HsWrapper, result) Source #
Variant of tcTopSkolemise
that takes an ExpType
:: CtOrigin | |
-> UserTypeCtxt | |
-> TcSigmaType | Actual |
-> ExpRhoType | Expected |
-> TcM HsWrapper |
tcSubTypeSigma :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper Source #
tcSubTypePat :: CtOrigin -> UserTypeCtxt -> ExpSigmaType -> TcSigmaType -> TcM HsWrapper Source #
tcSubTypeDS :: HsExpr GhcRn -> TcRhoType -> ExpRhoType -> TcM HsWrapper Source #
tcSubTypeAmbiguity :: UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper Source #
checkConstraints :: SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result) Source #
checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result Source #
buildImplicationFor :: TcLevel -> SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> WantedConstraints -> TcM (Bag Implication, TcEvBinds) Source #
buildTvImplication :: SkolemInfoAnon -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM Implication Source #
emitResidualTvConstraint :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM () Source #
:: Maybe TypedThing | If present, the thing that has type ty1 |
-> TcTauType | |
-> TcTauType | |
-> TcM TcCoercionN |
unifyExpectedType :: HsExpr GhcRn -> TcRhoType -> ExpRhoType -> TcM TcCoercionN Source #
promoteTcType :: TcLevel -> TcType -> TcM (TcCoercionN, TcType) Source #
startSolvingByUnification :: MetaInfo -> TcType -> TcM (Maybe TcType) Source #
Checks (TYVAR-TV), (COERCION-HOLE) and (CONCRETE) of Note [Unification preconditions]; returns True if these conditions are satisfied. But see the Note for other preconditions, too.
tcInfer :: (ExpSigmaType -> TcM a) -> TcM (a, TcSigmaType) Source #
Infer a type using a fresh ExpType See also Note [ExpType] in GHC.Tc.Utils.TcMType
Use tcInferFRR
if you require the type to have a fixed
runtime representation.
matchExpectedListTy :: TcRhoType -> TcM (TcCoercionN, TcRhoType) Source #
matchExpectedTyConApp :: TyCon -> TcRhoType -> TcM (TcCoercionN, [TcSigmaType]) Source #
matchExpectedAppTy :: TcRhoType -> TcM (TcCoercion, (TcSigmaType, TcSigmaType)) Source #
matchExpectedFunTys :: forall a. ExpectedFunTyOrigin -> UserTypeCtxt -> Arity -> ExpRhoType -> ([Scaled ExpSigmaTypeFRR] -> ExpRhoType -> TcM a) -> TcM (HsWrapper, a) Source #
Use this function to split off arguments types when you have an "expected" type.
This function skolemises at each polytype.
Invariant: this function only applies the provided function to a list of argument types which all have a syntactically fixed RuntimeRep in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete. See Note [Return arguments with a fixed RuntimeRep].
:: TypedThing | 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 Source #
:: ExpectedFunTyOrigin | See Note [Herald for matchExpectedFunTys] |
-> Maybe TypedThing | The thing with type TcSigmaType |
-> (Arity, [Scaled TcSigmaType]) | Total number of value args in the call, and types of values args to which function has been applied already (reversed) (Both are used only for error messages) |
-> TcRhoType | Type to analyse: a TcRhoType |
-> TcM (HsWrapper, Scaled TcSigmaTypeFRR, TcSigmaType) |
matchActualFunTySigma
looks for just one function arrow,
returning an uninstantiated sigma-type.
Invariant: the returned argument type has a syntactically fixed RuntimeRep in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
See Note [Return arguments with a fixed RuntimeRep].
:: ExpectedFunTyOrigin | See Note [Herald for matchExpectedFunTys] |
-> CtOrigin | |
-> Maybe TypedThing | the thing with type TcSigmaType |
-> Arity | |
-> TcSigmaType | |
-> TcM (HsWrapper, [Scaled TcSigmaTypeFRR], TcRhoType) |
Like matchExpectedFunTys
, but used when you have an "actual" type,
for example in function application.
INVARIANT: the returned argument types all have a syntactically fixed RuntimeRep in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete. See Note [Return arguments with a fixed RuntimeRep].
checkTyVarEq :: TcTyVar -> TcType -> CheckTyEqResult Source #
checkTyFamEq :: TyCon -> [TcType] -> TcType -> CheckTyEqResult Source #
checkTypeEq :: CanEqLHS -> TcType -> CheckTyEqResult Source #