ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Utils.Unify

Description

Type subsumption and unification

Synopsis

Documentation

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

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 tcTopSkolemise

tcSkolemiseExpType :: UserTypeCtxt -> ExpSigmaType -> (ExpRhoType -> TcM result) -> TcM (HsWrapper, result) Source #

Variant of tcTopSkolemise that takes an ExpType

tcSubType Source #

Arguments

:: CtOrigin 
-> UserTypeCtxt 
-> TcSigmaType

Actual

-> ExpRhoType

Expected

-> TcM HsWrapper 

checkConstraints :: SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result) Source #

checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result Source #

unifyType Source #

Arguments

:: Maybe TypedThing

If present, the thing that has type ty1

-> TcTauType 
-> TcTauType 
-> TcM TcCoercionN 

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.

matchExpectedFunTys :: 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].

matchExpectedFunKind Source #

Arguments

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

Arguments

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

matchActualFunTysRho Source #

Arguments

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

data PuResult a b Source #

Constructors

PuFail CheckTyEqResult 
PuOK (Bag a) b 

Instances

Instances details
Applicative (PuResult a) Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

pure :: a0 -> PuResult a a0 Source #

(<*>) :: PuResult a (a0 -> b) -> PuResult a a0 -> PuResult a b Source #

liftA2 :: (a0 -> b -> c) -> PuResult a a0 -> PuResult a b -> PuResult a c Source #

(*>) :: PuResult a a0 -> PuResult a b -> PuResult a b Source #

(<*) :: PuResult a a0 -> PuResult a b -> PuResult a a0 Source #

Functor (PuResult a) Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

fmap :: (a0 -> b) -> PuResult a a0 -> PuResult a b Source #

(<$) :: a0 -> PuResult a b -> PuResult a a0 Source #

(Outputable a, Outputable b) => Outputable (PuResult a b) Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

ppr :: PuResult a b -> SDoc Source #

data TyEqFlags a Source #

Options describing how to deal with a type equality in the pure unifier. See checkTyEqRhs

Instances

Instances details
Outputable (TyEqFlags a) Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

ppr :: TyEqFlags a -> SDoc Source #

data TyEqFamApp a Source #

What to do when encountering a type-family application while processing a type equality in the pure unifier.

See Note [Family applications in canonical constraints]

Instances

Instances details
Outputable (TyEqFamApp a) Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

ppr :: TyEqFamApp a -> SDoc Source #

data AreUnifying Source #

Instances

Instances details
Outputable AreUnifying Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

ppr :: AreUnifying -> SDoc Source #

data LevelCheck Source #

Constructors

LC_None 
LC_Check 
LC_Promote 

Instances

Instances details
Outputable LevelCheck Source # 
Instance details

Defined in GHC.Tc.Utils.Unify

Methods

ppr :: LevelCheck -> SDoc Source #