Safe Haskell | None |
---|---|
Language | GHC2021 |
Types used in the typechecker
This module provides the Type interface for front-end parts of the compiler. These parts
- treat "source types" as opaque: newtypes, and predicates are meaningful.
- look through usage types
Synopsis
- type TcType = Type
- type TcSigmaType = TcType
- type TcTypeFRR = TcType
- type TcSigmaTypeFRR = TcSigmaType
- type TcRhoType = TcType
- type TcTauType = TcType
- type TcPredType = PredType
- type TcThetaType = ThetaType
- type TcTyVar = Var
- type TcTyVarSet = TyVarSet
- type TcDTyVarSet = DTyVarSet
- type TcTyCoVarSet = TyCoVarSet
- type TcDTyCoVarSet = DTyCoVarSet
- type TcKind = Kind
- type TcCoVar = CoVar
- type TcTyCoVar = Var
- type TcTyVarBinder = TyVarBinder
- type TcInvisTVBinder = InvisTVBinder
- type TcReqTVBinder = ReqTVBinder
- type TcTyCon = TyCon
- type MonoTcTyCon = TcTyCon
- type PolyTcTyCon = TcTyCon
- type TcTyConBinder = TyConBinder
- type KnotTied (ty :: k) = ty
- data ExpType
- = Check TcType
- | Infer !InferResult
- data InferResult = IR {}
- type ExpTypeFRR = ExpType
- type ExpSigmaType = ExpType
- type ExpSigmaTypeFRR = ExpTypeFRR
- type ExpRhoType = ExpType
- mkCheckExpType :: TcType -> ExpType
- checkingExpType_maybe :: ExpType -> Maybe TcType
- checkingExpType :: ExpType -> TcType
- data ExpPatType
- mkCheckExpFunPatTy :: Scaled TcType -> ExpPatType
- mkInvisExpPatType :: InvisTyBinder -> ExpPatType
- isVisibleExpPatType :: ExpPatType -> Bool
- isExpFunPatType :: ExpPatType -> Bool
- data SyntaxOpType
- synKnownType :: TcType -> SyntaxOpType
- mkSynFunTys :: [SyntaxOpType] -> ExpType -> SyntaxOpType
- newtype TcLevel = TcLevel Int
- topTcLevel :: TcLevel
- pushTcLevel :: TcLevel -> TcLevel
- isTopTcLevel :: TcLevel -> Bool
- strictlyDeeperThan :: TcLevel -> TcLevel -> Bool
- deeperThanOrSame :: TcLevel -> TcLevel -> Bool
- sameDepthAs :: TcLevel -> TcLevel -> Bool
- tcTypeLevel :: TcType -> TcLevel
- tcTyVarLevel :: TcTyVar -> TcLevel
- maxTcLevel :: TcLevel -> TcLevel -> TcLevel
- minTcLevel :: TcLevel -> TcLevel -> TcLevel
- data TcTyVarDetails
- = SkolemTv SkolemInfo TcLevel Bool
- | RuntimeUnk
- | MetaTv { }
- pprTcTyVarDetails :: TcTyVarDetails -> SDoc
- vanillaSkolemTvUnk :: HasCallStack => TcTyVarDetails
- data MetaDetails
- data MetaInfo
- skolemSkolInfo :: TcTyVar -> SkolemInfo
- isImmutableTyVar :: TyVar -> Bool
- isSkolemTyVar :: TcTyVar -> Bool
- isMetaTyVar :: TcTyVar -> Bool
- isMetaTyVarTy :: TcType -> Bool
- isTyVarTy :: Type -> Bool
- tcIsTcTyVar :: TcTyVar -> Bool
- isTyVarTyVar :: Var -> Bool
- isOverlappableTyVar :: TcTyVar -> Bool
- isTyConableTyVar :: TcTyVar -> Bool
- data ConcreteTvOrigin = ConcreteFRR FixedRuntimeRepOrigin
- isConcreteTyVar_maybe :: TcTyVar -> Maybe ConcreteTvOrigin
- isConcreteTyVar :: TcTyVar -> Bool
- isConcreteTyVarTy :: TcType -> Bool
- isConcreteTyVarTy_maybe :: TcType -> Maybe (TcTyVar, ConcreteTvOrigin)
- isConcreteInfo :: MetaInfo -> Bool
- type ConcreteTyVars = NameEnv ConcreteTvOrigin
- noConcreteTyVars :: ConcreteTyVars
- isAmbiguousTyVar :: TcTyVar -> Bool
- isCycleBreakerTyVar :: TcTyVar -> Bool
- metaTyVarRef :: TyVar -> IORef MetaDetails
- metaTyVarInfo :: TcTyVar -> MetaInfo
- isFlexi :: MetaDetails -> Bool
- isIndirect :: MetaDetails -> Bool
- isRuntimeUnkSkol :: TyVar -> Bool
- metaTyVarTcLevel :: TcTyVar -> TcLevel
- setMetaTyVarTcLevel :: TcTyVar -> TcLevel -> TcTyVar
- metaTyVarTcLevel_maybe :: TcTyVar -> Maybe TcLevel
- isTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool
- isPromotableMetaTyVar :: TcTyVar -> Bool
- findDupTyVarTvs :: [(Name, TcTyVar)] -> [(Name, Name)]
- mkTyVarNamePairs :: [TyVar] -> [(Name, TyVar)]
- mkInfSigmaTy :: HasDebugCallStack => [TyCoVar] -> [PredType] -> Type -> Type
- mkSpecSigmaTy :: HasDebugCallStack => [TyVar] -> [PredType] -> Type -> Type
- mkSigmaTy :: HasDebugCallStack => [ForAllTyBinder] -> [PredType] -> Type -> Type
- mkPhiTy :: HasDebugCallStack => [PredType] -> Type -> Type
- tcMkPhiTy :: HasDebugCallStack => [PredType] -> Type -> Type
- tcMkDFunSigmaTy :: [TyVar] -> ThetaType -> Type -> Type
- tcMkDFunPhiTy :: HasDebugCallStack => [PredType] -> Type -> Type
- getTyVar :: HasDebugCallStack => Type -> TyVar
- getTyVar_maybe :: Type -> Maybe TyVar
- getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN)
- tcSplitForAllTyVarBinder_maybe :: Type -> Maybe (TyVarBinder, Type)
- tcSplitForAllTyVars :: Type -> ([TyVar], Type)
- tcSplitForAllInvisTyVars :: Type -> ([TyVar], Type)
- tcSplitSomeForAllTyVars :: (ForAllTyFlag -> Bool) -> Type -> ([TyVar], Type)
- tcSplitForAllReqTVBinders :: Type -> ([TcReqTVBinder], Type)
- tcSplitForAllInvisTVBinders :: Type -> ([TcInvisTVBinder], Type)
- tcSplitPiTys :: Type -> ([PiTyVarBinder], Type)
- tcSplitPiTy_maybe :: Type -> Maybe (PiTyVarBinder, Type)
- tcSplitForAllTyVarBinders :: Type -> ([TyVarBinder], Type)
- tcSplitPhiTy :: Type -> (ThetaType, Type)
- tcSplitPredFunTy_maybe :: Type -> Maybe (PredType, Type)
- tcSplitFunTy_maybe :: Type -> Maybe (Scaled Type, Type)
- tcSplitFunTys :: Type -> ([Scaled Type], Type)
- tcFunArgTy :: Type -> Scaled Type
- tcFunResultTy :: Type -> Type
- tcFunResultTyN :: HasDebugCallStack => Arity -> Type -> Type
- tcSplitFunTysN :: Arity -> TcRhoType -> Either Arity ([Scaled TcSigmaType], TcSigmaType)
- tcSplitTyConApp :: Type -> (TyCon, [Type])
- tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type])
- tcTyConAppTyCon :: Type -> TyCon
- tcTyConAppTyCon_maybe :: Type -> Maybe TyCon
- tcTyConAppArgs :: Type -> [Type]
- tcSplitAppTy_maybe :: Type -> Maybe (Type, Type)
- tcSplitAppTy :: Type -> (Type, Type)
- tcSplitAppTys :: Type -> (Type, [Type])
- tcSplitAppTyNoView_maybe :: Type -> Maybe (Type, Type)
- tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type)
- tcSplitSigmaTyBndrs :: Type -> ([TcInvisTVBinder], ThetaType, Type)
- tcSplitNestedSigmaTys :: Type -> ([TyVar], ThetaType, Type)
- tcSplitIOType_maybe :: Type -> Maybe (TyCon, Type)
- isSigmaTy :: TcType -> Bool
- isRhoTy :: TcType -> Bool
- isRhoExpTy :: ExpType -> Bool
- isOverloadedTy :: Type -> Bool
- isFloatingPrimTy :: Type -> Bool
- isDoubleTy :: Type -> Bool
- isFloatTy :: Type -> Bool
- isIntTy :: Type -> Bool
- isWordTy :: Type -> Bool
- isStringTy :: Type -> Bool
- isIntegerTy :: Type -> Bool
- isNaturalTy :: Type -> Bool
- isBoolTy :: Type -> Bool
- isUnitTy :: Type -> Bool
- isCharTy :: Type -> Bool
- isTauTy :: Type -> Bool
- isTauTyCon :: TyCon -> Bool
- tcIsTyVarTy :: Type -> Bool
- isPredTy :: HasDebugCallStack => Type -> Bool
- isTyVarClassPred :: PredType -> Bool
- checkValidClsArgs :: Bool -> Class -> [KindOrType] -> Bool
- hasTyVarHead :: Type -> Bool
- isRigidTy :: TcType -> Bool
- anyTy_maybe :: Type -> Maybe Kind
- eqType :: Type -> Type -> Bool
- eqTypes :: [Type] -> [Type] -> Bool
- nonDetCmpType :: Type -> Type -> Ordering
- nonDetCmpTypes :: [Type] -> [Type] -> Ordering
- eqTypeX :: RnEnv2 -> Type -> Type -> Bool
- pickyEqType :: Type -> Type -> Bool
- tcEqType :: HasDebugCallStack => Type -> Type -> Bool
- tcEqKind :: HasDebugCallStack => Kind -> Kind -> Bool
- tcEqTypeNoKindCheck :: Type -> Type -> Bool
- tcEqTypeVis :: Type -> Type -> Bool
- tcEqTyConApps :: TyCon -> [Type] -> TyCon -> [Type] -> Bool
- eqForAllVis :: ForAllTyFlag -> ForAllTyFlag -> Bool
- eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2
- deNoteType :: Type -> Type
- getDFunTyKey :: Type -> OccName
- evVarPred :: EvVar -> PredType
- ambigTkvsOfTy :: TcType -> ([Var], [Var])
- mkMinimalBySCs :: (a -> PredType) -> [a] -> [a]
- transSuperClasses :: PredType -> [PredType]
- pickCapturedPreds :: TyVarSet -> TcThetaType -> TcThetaType
- immSuperClasses :: Class -> [Type] -> [PredType]
- boxEqPred :: EqRel -> Type -> Type -> Maybe (Class, [Type])
- isImprovementPred :: PredType -> Bool
- tcTyFamInsts :: Type -> [(TyCon, [Type])]
- tcTyFamInstsAndVis :: Type -> [(Bool, TyCon, [Type])]
- tcTyConAppTyFamInstsAndVis :: TyCon -> [Type] -> [(Bool, TyCon, [Type])]
- isTyFamFree :: Type -> Bool
- exactTyCoVarsOfType :: Type -> TyCoVarSet
- exactTyCoVarsOfTypes :: [Type] -> TyCoVarSet
- anyRewritableTyVar :: EqRel -> (EqRel -> TcTyVar -> Bool) -> TcType -> Bool
- anyRewritableTyFamApp :: EqRel -> (EqRel -> TyCon -> [TcType] -> Bool) -> TcType -> Bool
- data PatersonSize
- data PatersonCondFailure
- data PatersonCondFailureContext
- ltPatersonSize :: PatersonSize -> PatersonSize -> Maybe PatersonCondFailure
- pSizeZero :: PatersonSize
- pSizeOne :: PatersonSize
- pSizeType :: Type -> PatersonSize
- pSizeTypeX :: VarSet -> Type -> PatersonSize
- pSizeTypes :: [Type] -> PatersonSize
- pSizeClassPred :: Class -> [Type] -> PatersonSize
- pSizeClassPredX :: VarSet -> Class -> [Type] -> PatersonSize
- pSizeTyConApp :: TyCon -> [Type] -> PatersonSize
- noMoreTyVars :: [TyVar] -> [TyVar] -> [TyVar]
- allDistinctTyVars :: TyVarSet -> [KindOrType] -> Bool
- type TypeSize = IntWithInf
- sizeType :: Type -> TypeSize
- sizeTypes :: [Type] -> TypeSize
- scopedSort :: [TyCoVar] -> [TyCoVar]
- isTerminatingClass :: Class -> Bool
- isStuckTypeFamily :: TyCon -> Bool
- type Kind = Type
- liftedTypeKind :: Type
- constraintKind :: Kind
- isLiftedTypeKind :: Kind -> Bool
- isUnliftedTypeKind :: Kind -> Bool
- isTYPEorCONSTRAINT :: Kind -> Bool
- data Type
- type PredType = Type
- type ThetaType = [PredType]
- data PiTyBinder
- data ForAllTyFlag where
- Invisible !Specificity
- Required
- pattern Specified :: ForAllTyFlag
- pattern Inferred :: ForAllTyFlag
- data FunTyFlag
- mkForAllTy :: ForAllTyBinder -> Type -> Type
- mkForAllTys :: [ForAllTyBinder] -> Type -> Type
- mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type
- mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type
- mkSpecForAllTys :: [TyVar] -> Type -> Type
- mkTyCoInvForAllTy :: TyCoVar -> Type -> Type
- mkInfForAllTy :: TyVar -> Type -> Type
- mkInfForAllTys :: [TyVar] -> Type -> Type
- mkVisFunTy :: HasDebugCallStack => Mult -> Type -> Type -> Type
- mkVisFunTyMany :: HasDebugCallStack => Type -> Type -> Type
- mkVisFunTysMany :: [Type] -> Type -> Type
- mkScaledFunTys :: HasDebugCallStack => [Scaled Type] -> Type -> Type
- mkInvisFunTy :: HasDebugCallStack => Type -> Type -> Type
- mkInvisFunTys :: HasDebugCallStack => [Type] -> Type -> Type
- mkTyConApp :: TyCon -> [Type] -> Type
- mkAppTy :: Type -> Type -> Type
- mkAppTys :: Type -> [Type] -> Type
- mkTyConTy :: TyCon -> Type
- mkTyVarTy :: TyVar -> Type
- mkTyVarTys :: [TyVar] -> [Type]
- mkTyCoVarTy :: TyCoVar -> Type
- mkTyCoVarTys :: [TyCoVar] -> [Type]
- isClassPred :: PredType -> Bool
- isEqPrimPred :: PredType -> Bool
- isIPLikePred :: Type -> Bool
- isEqPred :: PredType -> Bool
- isEqualityClass :: Class -> Bool
- mkClassPred :: Class -> [Type] -> PredType
- tcSplitQuantPredTy :: Type -> ([TyVar], [Type], PredType)
- tcSplitDFunTy :: Type -> ([TyVar], [Type], Class, [Type])
- tcSplitDFunHead :: Type -> (Class, [Type])
- tcSplitMethodTy :: Type -> ([TyVar], PredType, Type)
- isRuntimeRepVar :: TyVar -> Bool
- isFixedRuntimeRepKind :: HasDebugCallStack => Kind -> Bool
- isVisiblePiTyBinder :: PiTyBinder -> Bool
- isInvisiblePiTyBinder :: PiTyBinder -> Bool
- data Subst = Subst InScopeSet IdSubstEnv TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- emptySubst :: Subst
- mkEmptySubst :: InScopeSet -> Subst
- zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> Subst
- mkTvSubstPrs :: [(TyVar, Type)] -> Subst
- notElemSubst :: Var -> Subst -> Bool
- unionSubst :: Subst -> Subst -> Subst
- getTvSubstEnv :: Subst -> TvSubstEnv
- getSubstInScope :: Subst -> InScopeSet
- extendSubstInScope :: Subst -> Var -> Subst
- extendSubstInScopeList :: Subst -> [Var] -> Subst
- extendSubstInScopeSet :: Subst -> VarSet -> Subst
- extendTvSubstAndInScope :: Subst -> TyVar -> Type -> Subst
- lookupTyVar :: Subst -> TyVar -> Maybe Type
- extendTCvSubst :: Subst -> TyCoVar -> Type -> Subst
- substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar)
- extendTvSubst :: Subst -> TyVar -> Type -> Subst
- isInScope :: Var -> Subst -> Bool
- mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst
- mkTvSubst :: InScopeSet -> TvSubstEnv -> Subst
- zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv
- zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv
- substTy :: HasDebugCallStack => Subst -> Type -> Type
- substTys :: HasDebugCallStack => Subst -> [Type] -> [Type]
- substScaledTys :: HasDebugCallStack => Subst -> [Scaled Type] -> [Scaled Type]
- substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type
- substTyWithCoVars :: [CoVar] -> [Coercion] -> Type -> Type
- substTyAddInScope :: HasDebugCallStack => Subst -> Type -> Type
- substTyUnchecked :: Subst -> Type -> Type
- substTysUnchecked :: Subst -> [Type] -> [Type]
- substScaledTyUnchecked :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type
- substThetaUnchecked :: Subst -> ThetaType -> ThetaType
- substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type
- substCoUnchecked :: Subst -> Coercion -> Coercion
- substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion
- substTheta :: HasDebugCallStack => Subst -> ThetaType -> ThetaType
- isUnliftedType :: HasDebugCallStack => Type -> Bool
- isUnboxedTupleType :: Type -> Bool
- isPrimitiveType :: Type -> Bool
- coreView :: Type -> Maybe Type
- tyCoVarsOfType :: Type -> TyCoVarSet
- tyCoVarsOfTypes :: [Type] -> TyCoVarSet
- closeOverKinds :: TyCoVarSet -> TyCoVarSet
- tyCoFVsOfType :: Type -> FV
- tyCoFVsOfTypes :: [Type] -> FV
- tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
- tyCoVarsOfTypesDSet :: [Type] -> DTyCoVarSet
- closeOverKindsDSet :: DTyVarSet -> DTyVarSet
- tyCoVarsOfTypeList :: Type -> [TyCoVar]
- tyCoVarsOfTypesList :: [Type] -> [TyCoVar]
- noFreeVarsOfType :: Type -> Bool
- pprKind :: Kind -> SDoc
- pprParendKind :: Kind -> SDoc
- pprSigmaType :: Type -> SDoc
- pprType :: Type -> SDoc
- pprParendType :: Type -> SDoc
- pprTypeApp :: TyCon -> [Type] -> SDoc
- pprTheta :: ThetaType -> SDoc
- pprParendTheta :: ThetaType -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- pprClassPred :: Class -> [Type] -> SDoc
- pprTCvBndr :: ForAllTyBinder -> SDoc
- pprTCvBndrs :: [ForAllTyBinder] -> SDoc
- tyConVisibilities :: TyCon -> [Bool]
- isNextTyConArgVisible :: TyCon -> [Type] -> Bool
- isNextArgVisible :: TcType -> Bool
Documentation
type TcSigmaType = TcType Source #
type TcTypeFRR = TcType Source #
A type which has a syntactically fixed RuntimeRep as per Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
type TcSigmaTypeFRR = TcSigmaType Source #
A TcSigmaTypeFRR
is a TcSigmaType
which has a syntactically
fixed RuntimeRep
in the sense of Note [Fixed RuntimeRep]
in GHC.Tc.Utils.Concrete.
In particular, this means that:
typePrimRep
does not panic,typeLevity_maybe
does not returnNothing
.
This property is important in functions such as matchExpectedFunTys
, where
we want to provide argument types which have a known runtime representation.
See Note [Return arguments with a fixed RuntimeRep.
type TcPredType = PredType Source #
type TcThetaType = ThetaType Source #
type TcTyVarSet = TyVarSet Source #
type TcDTyVarSet = DTyVarSet Source #
type TcTyCoVarSet = TyCoVarSet Source #
type TcDTyCoVarSet = DTyCoVarSet Source #
type TcTyVarBinder = TyVarBinder Source #
type TcInvisTVBinder = InvisTVBinder Source #
type TcReqTVBinder = ReqTVBinder Source #
type MonoTcTyCon = TcTyCon Source #
type PolyTcTyCon = TcTyCon Source #
type TcTyConBinder = TyConBinder Source #
type KnotTied (ty :: k) = ty Source #
A type labeled KnotTied
might have knot-tied tycons in it. See
Note [Type checking recursive type and class declarations] in
GHC.Tc.TyCl
An expected type to check against during type-checking. See Note [ExpType] in GHC.Tc.Utils.TcMType, where you'll also find manipulators.
Instances
data InferResult Source #
IR | |
|
Instances
Outputable InferResult Source # | |
Defined in GHC.Tc.Utils.TcType ppr :: InferResult -> SDoc Source # |
type ExpTypeFRR = ExpType Source #
type ExpSigmaType = ExpType Source #
type ExpSigmaTypeFRR = ExpTypeFRR Source #
Like TcSigmaTypeFRR
, but for an expected type.
See ExpTypeFRR
.
type ExpRhoType = ExpType Source #
checkingExpType_maybe :: ExpType -> Maybe TcType Source #
Returns the expected type when in checking mode.
checkingExpType :: ExpType -> TcType Source #
Returns the expected type when in checking mode. Panics if in inference mode.
data ExpPatType Source #
Instances
Outputable ExpPatType Source # | |
Defined in GHC.Tc.Utils.TcType ppr :: ExpPatType -> SDoc Source # |
isVisibleExpPatType :: ExpPatType -> Bool Source #
isExpFunPatType :: ExpPatType -> Bool Source #
data SyntaxOpType Source #
What to expect for an argument to a rebindable-syntax operator.
Quite like Type
, but allows for holes to be filled in by tcSyntaxOp.
The callback called from tcSyntaxOp gets a list of types; the meaning
of these types is determined by a left-to-right depth-first traversal
of the SyntaxOpType
tree. So if you pass in
SynAny `SynFun` (SynList `SynFun` SynType Int) `SynFun` SynAny
you'll get three types back: one for the first SynAny
, the element
type of the list, and one for the last SynAny
. You don't get anything
for the SynType
, because you've said positively that it should be an
Int, and so it shall be.
You'll also get three multiplicities back: one for each function arrow. See also Note [Linear types] in Multiplicity.
This is defined here to avoid defining it in GHC.Tc.Gen.Expr boot file.
SynAny | Any type |
SynRho | A rho type, skolemised or instantiated as appropriate |
SynList | A list type. You get back the element type of the list |
SynFun SyntaxOpType SyntaxOpType infixr 0 | A function. |
SynType ExpType | A known type. |
synKnownType :: TcType -> SyntaxOpType Source #
Like SynType
but accepts a regular TcType
mkSynFunTys :: [SyntaxOpType] -> ExpType -> SyntaxOpType Source #
Like mkFunTys
but for SyntaxOpType
topTcLevel :: TcLevel Source #
pushTcLevel :: TcLevel -> TcLevel Source #
isTopTcLevel :: TcLevel -> Bool Source #
tcTypeLevel :: TcType -> TcLevel Source #
tcTyVarLevel :: TcTyVar -> TcLevel Source #
data TcTyVarDetails Source #
Instances
Outputable TcTyVarDetails Source # | |
Defined in GHC.Tc.Utils.TcType ppr :: TcTyVarDetails -> SDoc Source # |
data MetaDetails Source #
Instances
Outputable MetaDetails Source # | |
Defined in GHC.Tc.Utils.TcType ppr :: MetaDetails -> SDoc Source # |
What restrictions are on this metavariable around unification? These are checked in GHC.Tc.Utils.Unify.checkTopShape
TauTv | This MetaTv is an ordinary unification variable A TauTv is always filled in with a tau-type, which never contains any ForAlls. |
TyVarTv | A variant of TauTv, except that it should not be unified with a type, only with a type variable See Note [TyVarTv] in GHC.Tc.Utils.TcMType |
RuntimeUnkTv | A unification variable used in the GHCi debugger. It is allowed to unify with a polytype, unlike TauTv |
CycleBreakerTv | |
ConcreteTv ConcreteTvOrigin | A unification variable that can only be unified with a concrete type, in the sense of Note [Concrete types] in GHC.Tc.Utils.Concrete. See Note [ConcreteTv] in GHC.Tc.Utils.Concrete. See also Note [The Concrete mechanism] in GHC.Tc.Utils.Concrete for an overview of how this works in context. |
Instances
skolemSkolInfo :: TcTyVar -> SkolemInfo Source #
isImmutableTyVar :: TyVar -> Bool Source #
isSkolemTyVar :: TcTyVar -> Bool Source #
isMetaTyVar :: TcTyVar -> Bool Source #
isMetaTyVarTy :: TcType -> Bool Source #
tcIsTcTyVar :: TcTyVar -> Bool Source #
isTyVarTyVar :: Var -> Bool Source #
isOverlappableTyVar :: TcTyVar -> Bool Source #
isTyConableTyVar :: TcTyVar -> Bool Source #
data ConcreteTvOrigin Source #
What caused us to create a ConcreteTv
metavariable?
See Note [ConcreteTv] in GHC.Tc.Utils.Concrete.
ConcreteFRR FixedRuntimeRepOrigin | A See |
isConcreteTyVar_maybe :: TcTyVar -> Maybe ConcreteTvOrigin Source #
Is this type variable a concrete type variable, i.e.
it is a metavariable with ConcreteTv
MetaInfo
?
Returns the ConcreteTvOrigin
stored in the type variable
if so, or Nothing
otherwise.
isConcreteTyVar :: TcTyVar -> Bool Source #
Is this type variable a concrete type variable, i.e.
it is a metavariable with ConcreteTv
MetaInfo
?
isConcreteTyVarTy :: TcType -> Bool Source #
Is this type concrete type variable, i.e.
a metavariable with ConcreteTv
MetaInfo
?
isConcreteTyVarTy_maybe :: TcType -> Maybe (TcTyVar, ConcreteTvOrigin) Source #
Is this type a concrete type variable? If so, return
the associated TcTyVar
and ConcreteTvOrigin
.
isConcreteInfo :: MetaInfo -> Bool Source #
type ConcreteTyVars = NameEnv ConcreteTvOrigin Source #
A mapping from skolem type variable Name
to concreteness information,
See Note [Representation-polymorphism checking built-ins] in GHC.Tc.Gen.Head.
noConcreteTyVars :: ConcreteTyVars Source #
The Id
has no outer forall'd type variables which must be instantiated
to concrete types.
isAmbiguousTyVar :: TcTyVar -> Bool Source #
isCycleBreakerTyVar :: TcTyVar -> Bool Source #
metaTyVarRef :: TyVar -> IORef MetaDetails Source #
metaTyVarInfo :: TcTyVar -> MetaInfo Source #
isFlexi :: MetaDetails -> Bool Source #
isIndirect :: MetaDetails -> Bool Source #
isRuntimeUnkSkol :: TyVar -> Bool Source #
metaTyVarTcLevel :: TcTyVar -> TcLevel Source #
isPromotableMetaTyVar :: TcTyVar -> Bool Source #
mkInfSigmaTy :: HasDebugCallStack => [TyCoVar] -> [PredType] -> Type -> Type Source #
Make a sigma ty where all type variables are Inferred
. That is,
they cannot be used with visible type application.
mkSpecSigmaTy :: HasDebugCallStack => [TyVar] -> [PredType] -> Type -> Type Source #
Make a sigma ty where all type variables are "specified". That is, they can be used with visible type application
mkSigmaTy :: HasDebugCallStack => [ForAllTyBinder] -> [PredType] -> Type -> Type Source #
tcMkDFunPhiTy :: HasDebugCallStack => [PredType] -> Type -> Type Source #
getTyVar :: HasDebugCallStack => Type -> TyVar Source #
Attempts to obtain the type variable underlying a Type
, and panics with the
given message if this is not a type variable type. See also getTyVar_maybe
getTyVar_maybe :: Type -> Maybe TyVar Source #
Attempts to obtain the type variable underlying a Type
getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) Source #
If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind ty
tcSplitForAllTyVars :: Type -> ([TyVar], Type) Source #
Like tcSplitPiTys
, but splits off only named binders,
returning just the tyvars.
tcSplitForAllInvisTyVars :: Type -> ([TyVar], Type) Source #
Like tcSplitForAllTyVars
, but only splits ForAllTy
s with Invisible
type variable binders.
tcSplitSomeForAllTyVars :: (ForAllTyFlag -> Bool) -> Type -> ([TyVar], Type) Source #
Like tcSplitForAllTyVars
, but only splits a ForAllTy
if argf_pred argf
is True
, where argf
is the visibility of the ForAllTy
's binder and
argf_pred
is a predicate over visibilities provided as an argument to this
function.
tcSplitForAllReqTVBinders :: Type -> ([TcReqTVBinder], Type) Source #
Like tcSplitForAllTyVars
, but only splits ForAllTy
s with Required
type
variable binders. All split tyvars are annotated with ()
.
tcSplitForAllInvisTVBinders :: Type -> ([TcInvisTVBinder], Type) Source #
Like tcSplitForAllTyVars
, but only splits ForAllTy
s with Invisible
type
variable binders. All split tyvars are annotated with their Specificity
.
tcSplitPiTys :: Type -> ([PiTyVarBinder], Type) Source #
Splits a forall type into a list of PiTyVarBinder
s and the inner type.
Always succeeds, even if it returns an empty list.
tcSplitPiTy_maybe :: Type -> Maybe (PiTyVarBinder, Type) Source #
Splits a type into a PiTyVarBinder and a body, if possible.
tcSplitForAllTyVarBinders :: Type -> ([TyVarBinder], Type) Source #
Like tcSplitForAllTyVars
, but splits off only named binders.
tcFunResultTy :: Type -> Type Source #
tcFunResultTyN :: HasDebugCallStack => Arity -> Type -> Type Source #
Strips off n *visible* arguments and returns the resulting type
tcSplitFunTysN :: Arity -> TcRhoType -> Either Arity ([Scaled TcSigmaType], TcSigmaType) Source #
Split off exactly the specified number argument types
Returns
(Left m) if there are m
missing arrows in the type
(Right (tys,res)) if the type looks like t1 -> ... -> tn -> res
tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) Source #
tcSplitTyConApp_maybe splits a type constructor application into its type constructor and applied types.
Differs from splitTyConApp_maybe in that it does *not* split types headed with (=>), as that's not a TyCon in the type-checker.
Note that this may fail (in funTyConAppTy_maybe) in the case
of a FunTy
with an argument of unknown kind FunTy
(e.g. `FunTy (a :: k) Int`, since the kind of a
isn't of
the form `TYPE rep`. This isn't usually a problem but may
be temporarily the case during canonicalization:
see Note [Decomposing FunTy] in GHC.Tc.Solver.Equality
and Note [The Purely Kinded Type Invariant (PKTI)] in GHC.Tc.Gen.HsType,
Wrinkle around FunTy
Consequently, you may need to zonk your type before using this function.
tcTyConAppTyCon :: Type -> TyCon Source #
tcTyConAppTyCon_maybe :: Type -> Maybe TyCon Source #
Like tcRepSplitTyConApp_maybe
, but only returns the TyCon
.
tcTyConAppArgs :: Type -> [Type] Source #
tcSplitAppTyNoView_maybe :: Type -> Maybe (Type, Type) Source #
Just like splitAppTyNoView_maybe, but does not split (c => t) See Note [Decomposing fat arrow c=>t]
tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type) Source #
Split a sigma type into its parts. This only splits invisible type variable binders, as these are the only forms of binder that the typechecker will implicitly instantiate.
tcSplitSigmaTyBndrs :: Type -> ([TcInvisTVBinder], ThetaType, Type) Source #
tcSplitNestedSigmaTys :: Type -> ([TyVar], ThetaType, Type) Source #
Split a sigma type into its parts, going underneath as many arrows and foralls as possible. See Note [tcSplitNestedSigmaTys]
isOverloadedTy :: Type -> Bool Source #
isFloatingPrimTy :: Type -> Bool Source #
Is the type inhabited by machine floating-point numbers?
Used to check that we don't use floating-point literal patterns in Core.
See #9238 and Note [Rules for floating-point comparisons] in GHC.Core.Opt.ConstantFold.
isDoubleTy :: Type -> Bool Source #
isIntegerTy :: Type -> Bool Source #
isNaturalTy :: Type -> Bool Source #
isTauTyCon :: TyCon -> Bool Source #
tcIsTyVarTy :: Type -> Bool Source #
isTyVarClassPred :: PredType -> Bool Source #
checkValidClsArgs :: Bool -> Class -> [KindOrType] -> Bool Source #
hasTyVarHead :: Type -> Bool Source #
anyTy_maybe :: Type -> Maybe Kind Source #
Check whether the type is of the form Any :: k
,
returning the kind k
.
eqType :: Type -> Type -> Bool Source #
Type equality on source types. Does not look through newtypes
,
PredType
s or type families, but it does look through type synonyms.
This first checks that the kinds of the types are equal and then
checks whether the types are equal, ignoring casts and coercions.
(The kind check is a recursive call, but since all kinds have type
Type
, there is no need to check the types of kinds.)
See also Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep.
eqTypes :: [Type] -> [Type] -> Bool Source #
Type equality on lists of types, looking through type synonyms but not newtypes.
eqTypeX :: RnEnv2 -> Type -> Type -> Bool Source #
Compare types with respect to a (presumably) non-empty RnEnv2
.
tcEqType :: HasDebugCallStack => Type -> Type -> Bool Source #
tcEqType implements typechecker equality It behaves just like eqType, but is implemented differently (for now)
tcEqTypeNoKindCheck :: Type -> Type -> Bool Source #
Just like tcEqType
, but will return True for types of different kinds
as long as their non-coercion structure is identical.
tcEqTypeVis :: Type -> Type -> Bool Source #
Like tcEqType
, but returns True if the visible part of the types
are equal, even if they are really unequal (in the invisible bits)
tcEqTyConApps :: TyCon -> [Type] -> TyCon -> [Type] -> Bool Source #
Check whether two TyConApps are the same; if the number of arguments are different, just checks the common prefix of arguments.
eqForAllVis :: ForAllTyFlag -> ForAllTyFlag -> Bool Source #
deNoteType :: Type -> Type Source #
getDFunTyKey :: Type -> OccName Source #
ambigTkvsOfTy :: TcType -> ([Var], [Var]) Source #
Returns the (kind, type) variables in a type that are as-yet-unknown: metavariables and RuntimeUnks
mkMinimalBySCs :: (a -> PredType) -> [a] -> [a] Source #
transSuperClasses :: PredType -> [PredType] Source #
pickCapturedPreds :: TyVarSet -> TcThetaType -> TcThetaType Source #
isImprovementPred :: PredType -> Bool Source #
Finding type instances
tcTyFamInsts :: Type -> [(TyCon, [Type])] Source #
Finds outermost type-family applications occurring in a type, after expanding synonyms. In the list (F, tys) that is returned we guarantee that tys matches F's arity. For example, given type family F a :: * -> * (arity 1) calling tcTyFamInsts on (Maybe (F Int Bool) will return (F, [Int]), not (F, [Int,Bool])
This is important for its use in deciding termination of type instances (see #11581). E.g. type instance G [Int] = ...(F Int <big type>)... we don't need to take <big type> into account when asking if the calls on the RHS are smaller than the LHS
tcTyFamInstsAndVis :: Type -> [(Bool, TyCon, [Type])] Source #
Like tcTyFamInsts
, except that the output records whether the
type family and its arguments occur as an invisible argument in
some type application. This information is useful because it helps GHC know
when to turn on -fprint-explicit-kinds
during error reporting so that
users can actually see the type family being mentioned.
As an example, consider:
class C a data T (a :: k) type family F a :: k instance C (T @(F Int) (F Bool))
There are two occurrences of the type family F
in that C
instance, so
will return:tcTyFamInstsAndVis
(C (T @(F Int) (F Bool)))
[ (True
, F, [Int]) , (False
, F, [Bool]) ]
F Int
is paired with True
since it appears as an invisible argument
to C
, whereas F Bool
is paired with False
since it appears an a
visible argument to C
.
See also Note [Kind arguments in error messages]
in GHC.Tc.Errors.
tcTyConAppTyFamInstsAndVis :: TyCon -> [Type] -> [(Bool, TyCon, [Type])] Source #
In an application of a TyCon
to some arguments, find the outermost
occurrences of type family applications within the arguments. This function
will not consider the TyCon
itself when checking for type family
applications.
See tcTyFamInstsAndVis
for more details on how this works (as this
function is called inside of tcTyFamInstsAndVis
).
isTyFamFree :: Type -> Bool Source #
Check that a type does not contain any type family applications.
Finding "exact" (non-dead) type variables
exactTyCoVarsOfType :: Type -> TyCoVarSet Source #
exactTyCoVarsOfTypes :: [Type] -> TyCoVarSet Source #
data PatersonSize Source #
The Paterson size of a given type, in the sense of Note [Paterson conditions] in GHC.Tc.Validity
- after expanding synonyms,
- ignoring coercions (as they are not user written).
PS_TyFam TyCon | The type mentions a type family, so the size could be anything. |
PS_Vanilla | The type does not mention a type family. |
Instances
Outputable PatersonSize Source # | |
Defined in GHC.Tc.Utils.TcType ppr :: PatersonSize -> SDoc Source # |
data PatersonCondFailure Source #
Why did the Paterson conditions fail; that is, why was the context P not Paterson-smaller than the head H?
See Note [Paterson conditions] in GHC.Tc.Validity.
PCF_TyVar | Some type variables occur more often in P than in H. See (PC1) in Note [Paterson conditions] in GHC.Tc.Validity. |
| |
PCF_Size | |
PCF_TyFam | P contains a type family. See (PC3) in Note [Paterson conditions] in GHC.Tc.Validity. |
|
data PatersonCondFailureContext Source #
Indicates whether a Paterson condition failure occurred in an instance declaration or a type family equation. Useful for differentiating context in error messages.
ltPatersonSize :: PatersonSize -> PatersonSize -> Maybe PatersonCondFailure Source #
ltPatersonSize ps1 ps2
returns:
Nothing
iffps1
is definitely strictly smaller thanps2
,Just ps_fail
otherwise;ps_fail
says what went wrong.
pSizeType :: Type -> PatersonSize Source #
pSizeTypeX :: VarSet -> Type -> PatersonSize Source #
pSizeTypes :: [Type] -> PatersonSize Source #
pSizeClassPred :: Class -> [Type] -> PatersonSize Source #
pSizeClassPredX :: VarSet -> Class -> [Type] -> PatersonSize Source #
pSizeTyConApp :: TyCon -> [Type] -> PatersonSize Source #
allDistinctTyVars :: TyVarSet -> [KindOrType] -> Bool Source #
type TypeSize = IntWithInf Source #
scopedSort :: [TyCoVar] -> [TyCoVar] Source #
Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]
This is a deterministic sorting operation (that is, doesn't depend on Uniques).
It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in GHC.Rename.HsType
isTerminatingClass :: Class -> Bool Source #
When this says True, ignore this class constraint during a termination check See (PS1) in Note [The PatersonSize of a type]
isStuckTypeFamily :: TyCon -> Bool Source #
isLiftedTypeKind :: Kind -> Bool Source #
Returns True if the argument is (lifted) Type or Constraint See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim
isUnliftedTypeKind :: Kind -> Bool Source #
Returns True if the kind classifies unlifted types (like 'Int#') and False otherwise. Note that this returns False for representation-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
isTYPEorCONSTRAINT :: Kind -> Bool Source #
Does this classify a type allowed to have values? Responds True to things like *, TYPE Lifted, TYPE IntRep, TYPE v, Constraint.
True of a kind `TYPE _` or `CONSTRAINT _`
Instances
Outputable Type Source # | |
Data Type Source # | |
Defined in GHC.Core.TyCo.Rep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
Eq (DeBruijn Type) Source # | |
A type of the form p
of constraint kind represents a value whose type is
the Haskell predicate p
, where a predicate is what occurs before
the =>
in a Haskell type.
We use PredType
as documentation to mark those types that we guarantee to
have this kind.
It can be expanded into its representation, but:
- The type checker must treat it as opaque
- The rest of the compiler treats it as transparent
Consider these examples:
f :: (Eq a) => a -> Int g :: (?x :: Int -> Int) => a -> Int h :: (r\l) => {r} => {l::Int | r}
Here the Eq a
and ?x :: Int -> Int
and rl
are all called "predicates"
data PiTyBinder Source #
A PiTyBinder
represents an argument to a function. PiTyBinders can be
dependent (Named
) or nondependent (Anon
). They may also be visible or
not. See Note [PiTyBinders]
Instances
Outputable PiTyBinder Source # | |
Defined in GHC.Types.Var ppr :: PiTyBinder -> SDoc Source # | |
Data PiTyBinder Source # | |
Defined in GHC.Types.Var gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PiTyBinder -> c PiTyBinder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PiTyBinder # toConstr :: PiTyBinder -> Constr # dataTypeOf :: PiTyBinder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PiTyBinder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PiTyBinder) # gmapT :: (forall b. Data b => b -> b) -> PiTyBinder -> PiTyBinder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PiTyBinder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PiTyBinder -> r # gmapQ :: (forall d. Data d => d -> u) -> PiTyBinder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PiTyBinder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # |
data ForAllTyFlag Source #
ForAllTyFlag
Is something required to appear in source Haskell (Required
),
permitted by request (Specified
) (visible type application), or
prohibited entirely from appearing in source Haskell (Inferred
)?
See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep
pattern Specified :: ForAllTyFlag | |
pattern Inferred :: ForAllTyFlag |
Instances
The non-dependent version of ForAllTyFlag
.
See Note [FunTyFlag]
Appears here partly so that it's together with its friends ForAllTyFlag
and ForallVisFlag, but also because it is used in IfaceType, rather
early in the compilation chain
Instances
Binary FunTyFlag Source # | |
Outputable FunTyFlag Source # | |
Data FunTyFlag Source # | |
Defined in GHC.Types.Var gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunTyFlag -> c FunTyFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunTyFlag # toConstr :: FunTyFlag -> Constr # dataTypeOf :: FunTyFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunTyFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunTyFlag) # gmapT :: (forall b. Data b => b -> b) -> FunTyFlag -> FunTyFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunTyFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunTyFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> FunTyFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunTyFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # | |
Eq FunTyFlag Source # | |
Ord FunTyFlag Source # | |
Defined in GHC.Types.Var |
mkForAllTy :: ForAllTyBinder -> Type -> Type Source #
Like mkTyCoForAllTy
, but does not check the occurrence of the binder
See Note [Unused coercion variable in ForAllTy]
mkForAllTys :: [ForAllTyBinder] -> Type -> Type Source #
Wraps foralls over the type using the provided TyCoVar
s from left to right
mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type Source #
Wraps foralls over the type using the provided InvisTVBinder
s from left to right
mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type Source #
Like mkForAllTys
, but assumes all variables are dependent and
Inferred
, a common case
mkSpecForAllTys :: [TyVar] -> Type -> Type Source #
Like mkForAllTys
, but assumes all variables are dependent and
Specified
, a common case
mkTyCoInvForAllTy :: TyCoVar -> Type -> Type Source #
Make a dependent forall over an Inferred
variable
mkInfForAllTy :: TyVar -> Type -> Type Source #
Like mkTyCoInvForAllTy
, but tv should be a tyvar
mkInfForAllTys :: [TyVar] -> Type -> Type Source #
Like mkTyCoInvForAllTys
, but tvs should be a list of tyvar
mkVisFunTy :: HasDebugCallStack => Mult -> Type -> Type -> Type Source #
mkVisFunTyMany :: HasDebugCallStack => Type -> Type -> Type infixr 3 Source #
Make nested arrow types | Special, common, case: Arrow type with mult Many
mkScaledFunTys :: HasDebugCallStack => [Scaled Type] -> Type -> Type Source #
mkInvisFunTy :: HasDebugCallStack => Type -> Type -> Type infixr 3 Source #
mkInvisFunTys :: HasDebugCallStack => [Type] -> Type -> Type Source #
mkTyConTy :: TyCon -> Type Source #
(mkTyConTy tc) returns (TyConApp tc []) but arranges to share that TyConApp among all calls See Note [Sharing nullary TyConApps] So it's just an alias for tyConNullaryTy!
mkTyVarTys :: [TyVar] -> [Type] Source #
mkTyCoVarTy :: TyCoVar -> Type Source #
mkTyCoVarTys :: [TyCoVar] -> [Type] Source #
isClassPred :: PredType -> Bool Source #
isEqPrimPred :: PredType -> Bool Source #
isIPLikePred :: Type -> Bool Source #
isEqualityClass :: Class -> Bool Source #
isRuntimeRepVar :: TyVar -> Bool Source #
Is a tyvar of type RuntimeRep
?
isFixedRuntimeRepKind :: HasDebugCallStack => Kind -> Bool Source #
Checks that a kind of the form Type
, Constraint
or 'TYPE r
is concrete. See isConcreteType
.
Precondition: The type has kind `TYPE blah` or `CONSTRAINT blah`
isVisiblePiTyBinder :: PiTyBinder -> Bool Source #
Does this binder bind a visible argument?
isInvisiblePiTyBinder :: PiTyBinder -> Bool Source #
Does this binder bind an invisible argument?
Type & coercion & id substitution
The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.
Instances
emptySubst :: Subst Source #
mkEmptySubst :: InScopeSet -> Subst Source #
zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> Subst Source #
Generates the in-scope set for the Subst
from the types in the incoming
environment. No CoVars or Ids, please!
mkTvSubstPrs :: [(TyVar, Type)] -> Subst Source #
Generates the in-scope set for the TCvSubst
from the types in the
incoming environment. No CoVars, please! The InScopeSet is just a thunk
so with a bit of luck it'll never be evaluated
getTvSubstEnv :: Subst -> TvSubstEnv Source #
getSubstInScope :: Subst -> InScopeSet Source #
Find the in-scope set: see Note [The substitution invariant]
extendSubstInScopeList :: Subst -> [Var] -> Subst Source #
Add the Var
s to the in-scope set: see also extendInScope
extendSubstInScopeSet :: Subst -> VarSet -> Subst Source #
Add the Var
s to the in-scope set: see also extendInScope
substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar) Source #
mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst Source #
mkTvSubst :: InScopeSet -> TvSubstEnv -> Subst Source #
Make a TCvSubst with specified tyvar subst and empty covar subst
zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv Source #
The InScopeSet is just a thunk so with a bit of luck it'll never be evaluated
zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv Source #
substTy :: HasDebugCallStack => Subst -> Type -> Type Source #
Substitute within a Type
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTys :: HasDebugCallStack => Subst -> [Type] -> [Type] Source #
Substitute within several Type
s
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substScaledTys :: HasDebugCallStack => Subst -> [Scaled Type] -> [Scaled Type] Source #
substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type Source #
Type substitution, see zipTvSubst
substTyAddInScope :: HasDebugCallStack => Subst -> Type -> Type Source #
Substitute within a Type
after adding the free variables of the type
to the in-scope set. This is useful for the case when the free variables
aren't already in the in-scope set or easily available.
See also Note [The substitution invariant].
substTyUnchecked :: Subst -> Type -> Type Source #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substTysUnchecked :: Subst -> [Type] -> [Type] Source #
Substitute within several Type
s disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTysUnchecked to
substTys and remove this function. Please don't use in new code.
substScaledTyUnchecked :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type Source #
substThetaUnchecked :: Subst -> ThetaType -> ThetaType Source #
Substitute within a ThetaType
disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substThetaUnchecked to
substTheta and remove this function. Please don't use in new code.
substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type Source #
Type substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substCoUnchecked :: Subst -> Coercion -> Coercion Source #
Substitute within a Coercion
disabling sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion Source #
Coercion substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTheta :: HasDebugCallStack => Subst -> ThetaType -> ThetaType Source #
Substitute within a ThetaType
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
isUnliftedType :: HasDebugCallStack => Type -> Bool Source #
Is the given type definitely unlifted? See Type for what an unlifted type is.
Panics on representation-polymorphic types; See mightBeUnliftedType
for
a more approximate predicate that behaves better in the presence of
representation polymorphism.
isUnboxedTupleType :: Type -> Bool Source #
isPrimitiveType :: Type -> Bool Source #
Returns true of types that are opaque to Haskell.
coreView :: Type -> Maybe Type Source #
This function strips off the top layer only of a type synonym
application (if any) its underlying representation type.
Returns Nothing
if there is nothing to look through.
This function does not look through type family applications.
By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing
tyCoVarsOfType :: Type -> TyCoVarSet Source #
tyCoVarsOfTypes :: [Type] -> TyCoVarSet Source #
tyCoFVsOfType :: Type -> FV Source #
The worker for tyCoFVsOfType
and tyCoFVsOfTypeList
.
The previous implementation used unionVarSet
which is O(n+m) and can
make the function quadratic.
It's exported, so that it can be composed with
other functions that compute free variables.
See Note [FV naming conventions] in GHC.Utils.FV.
Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in GHC.Utils.FV for explanation.
tyCoFVsOfTypes :: [Type] -> FV Source #
tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet Source #
tyCoFVsOfType
that returns free variables of a type in a deterministic
set. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfTypesDSet :: [Type] -> DTyCoVarSet Source #
Returns free variables of types, including kind variables as a deterministic set. For type synonyms it does not expand the synonym.
closeOverKindsDSet :: DTyVarSet -> DTyVarSet Source #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.
tyCoVarsOfTypeList :: Type -> [TyCoVar] Source #
tyCoFVsOfType
that returns free variables of a type in deterministic
order. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in GHC.Utils.FV.
tyCoVarsOfTypesList :: [Type] -> [TyCoVar] Source #
Returns free variables of types, including kind variables as a deterministically ordered list. For type synonyms it does not expand the synonym.
noFreeVarsOfType :: Type -> Bool Source #
pprParendKind :: Kind -> SDoc Source #
pprSigmaType :: Type -> SDoc Source #
pprParendType :: Type -> SDoc Source #
pprParendTheta :: ThetaType -> SDoc Source #
pprThetaArrowTy :: ThetaType -> SDoc Source #
pprTCvBndr :: ForAllTyBinder -> SDoc Source #
pprTCvBndrs :: [ForAllTyBinder] -> SDoc Source #
tyConVisibilities :: TyCon -> [Bool] Source #
For every arg a tycon can take, the returned list says True if the argument is taken visibly, and False otherwise. Ends with an infinite tail of Trues to allow for oversaturation.
isNextTyConArgVisible :: TyCon -> [Type] -> Bool Source #
If the tycon is applied to the types, is the next argument visible?
isNextArgVisible :: TcType -> Bool Source #
Should this type be applied to a visible argument?
E.g. (s t): is t
a visible argument of s
?