ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Utils.Unify

Description

Type subsumption and unification

Synopsis

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 #

tcSkolemise Source #

Arguments

:: 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

tcSkolemiseScoped Source #

Arguments

:: 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 #

tcSubMult :: CtOrigin -> Mult -> Mult -> 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 #

unifyType Source #

Arguments

:: Maybe SDoc

If present, the thing that has type ty1

-> TcTauType 
-> TcTauType 
-> TcM TcCoercionN 

uType :: TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM CoercionN 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 #

matchExpectedFunKind Source #

Arguments

:: 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 #