| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
TcMType
Synopsis
- type TcTyVar = Var
- type TcKind = Kind
- type TcType = Type
- type TcTauType = TcType
- type TcThetaType = ThetaType
- type TcTyVarSet = TyVarSet
- newFlexiTyVar :: Kind -> TcM TcTyVar
- newFlexiTyVarTy :: Kind -> TcM TcType
- newFlexiTyVarTys :: Int -> Kind -> TcM [TcType]
- newOpenFlexiTyVarTy :: TcM TcType
- newOpenTypeKind :: TcM TcKind
- newMetaKindVar :: TcM TcKind
- newMetaKindVars :: Int -> TcM [TcKind]
- newMetaTyVarTyAtLevel :: TcLevel -> TcKind -> TcM TcType
- cloneMetaTyVar :: TcTyVar -> TcM TcTyVar
- newFmvTyVar :: TcType -> TcM TcTyVar
- newFskTyVar :: TcType -> TcM TcTyVar
- readMetaTyVar :: TyVar -> TcM MetaDetails
- writeMetaTyVar :: TcTyVar -> TcType -> TcM ()
- newMetaDetails :: MetaInfo -> TcM TcTyVarDetails
- isFilledMetaTyVar :: TyVar -> TcM Bool
- isUnfilledMetaTyVar :: TyVar -> TcM Bool
- data ExpType- = Check TcType
- | Infer !InferResult
 
- type ExpSigmaType = ExpType
- type ExpRhoType = ExpType
- mkCheckExpType :: TcType -> ExpType
- newInferExpType :: Bool -> TcM ExpType
- newInferExpTypeInst :: TcM ExpRhoType
- newInferExpTypeNoInst :: TcM ExpSigmaType
- readExpType :: ExpType -> TcM TcType
- readExpType_maybe :: ExpType -> TcM (Maybe TcType)
- expTypeToType :: ExpType -> TcM TcType
- checkingExpType_maybe :: ExpType -> Maybe TcType
- checkingExpType :: String -> ExpType -> TcType
- tauifyExpType :: ExpType -> TcM ExpType
- inferResultToType :: InferResult -> TcM Type
- genInstSkolTyVarsX :: SrcSpan -> TCvSubst -> [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar])
- newEvVar :: TcPredType -> TcRnIf gbl lcl EvVar
- newEvVars :: TcThetaType -> TcM [EvVar]
- newDict :: Class -> [TcType] -> TcM DictId
- newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence
- newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence]
- cloneWanted :: Ct -> TcM CtEvidence
- cloneSimple :: Ct -> TcM Ct
- cloneWC :: WantedConstraints -> TcM WantedConstraints
- emitWanted :: CtOrigin -> TcPredType -> TcM EvTerm
- emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion
- emitWantedEvVar :: CtOrigin -> TcPredType -> TcM EvVar
- emitWantedEvVars :: CtOrigin -> [TcPredType] -> TcM [EvVar]
- newTcEvBinds :: TcM EvBindsVar
- newNoTcEvBinds :: TcM EvBindsVar
- addTcEvBind :: EvBindsVar -> EvBind -> TcM ()
- newCoercionHole :: TcPredType -> TcM CoercionHole
- fillCoercionHole :: CoercionHole -> Coercion -> TcM ()
- isFilledCoercionHole :: CoercionHole -> TcM Bool
- unpackCoercionHole :: CoercionHole -> TcM Coercion
- unpackCoercionHole_maybe :: CoercionHole -> TcM (Maybe Coercion)
- checkCoercionHole :: CoVar -> Coercion -> TcM Coercion
- newMetaTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- newMetaTyVarX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar)
- newMetaTyVarsX :: TCvSubst -> [TyVar] -> TcM (TCvSubst, [TcTyVar])
- newMetaSigTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- newMetaSigTyVarX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar)
- newSigTyVar :: Name -> Kind -> TcM TcTyVar
- newSkolemTyVar :: Name -> Kind -> TcM TcTyVar
- newWildCardX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar)
- tcInstType :: ([TyVar] -> TcM (TCvSubst, [TcTyVar])) -> Id -> TcM ([(Name, TcTyVar)], TcThetaType, TcType)
- tcInstSkolTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- tcInstSkolTyVarsX :: TCvSubst -> [TyVar] -> TcM (TCvSubst, [TcTyVar])
- tcInstSuperSkolTyVarsX :: TCvSubst -> [TyVar] -> TcM (TCvSubst, [TcTyVar])
- tcSkolDFunType :: DFunId -> TcM ([TcTyVar], TcThetaType, TcType)
- tcSuperSkolTyVars :: [TyVar] -> (TCvSubst, [TcTyVar])
- instSkolTyCoVarsX :: TcTyCoVarMaker gbl lcl -> TCvSubst -> [TyCoVar] -> TcRnIf gbl lcl (TCvSubst, [TyCoVar])
- freshenTyVarBndrs :: [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TyVar])
- freshenCoVarBndrsX :: TCvSubst -> [CoVar] -> TcRnIf gbl lcl (TCvSubst, [CoVar])
- zonkTidyTcType :: TidyEnv -> TcType -> TcM (TidyEnv, TcType)
- zonkTidyTcTypes :: TidyEnv -> [TcType] -> TcM (TidyEnv, [TcType])
- zonkTidyOrigin :: TidyEnv -> CtOrigin -> TcM (TidyEnv, CtOrigin)
- tidyEvVar :: TidyEnv -> EvVar -> EvVar
- tidyCt :: TidyEnv -> Ct -> Ct
- tidySkolemInfo :: TidyEnv -> SkolemInfo -> SkolemInfo
- skolemiseRuntimeUnk :: TcTyVar -> TcM TyVar
- zonkTcTyVar :: TcTyVar -> TcM TcType
- zonkTcTyVars :: [TcTyVar] -> TcM [TcType]
- zonkTcTyVarToTyVar :: HasDebugCallStack => TcTyVar -> TcM TcTyVar
- zonkSigTyVarPairs :: [(Name, TcTyVar)] -> TcM [(Name, TcTyVar)]
- zonkTyCoVarsAndFV :: TyCoVarSet -> TcM TyCoVarSet
- zonkTcTypeAndFV :: TcType -> TcM DTyCoVarSet
- zonkTyCoVarsAndFVList :: [TyCoVar] -> TcM [TyCoVar]
- zonkTcTypeAndSplitDepVars :: TcType -> TcM CandidatesQTvs
- zonkTcTypesAndSplitDepVars :: [TcType] -> TcM CandidatesQTvs
- zonkQuantifiedTyVar :: TcTyVar -> TcM TcTyVar
- defaultTyVar :: Bool -> TcTyVar -> TcM Bool
- quantifyTyVars :: TcTyCoVarSet -> CandidatesQTvs -> TcM [TcTyVar]
- zonkTcTyCoVarBndr :: TcTyCoVar -> TcM TcTyCoVar
- zonkTcTyVarBinder :: TyVarBndr TcTyVar vis -> TcM (TyVarBndr TcTyVar vis)
- zonkTcType :: TcType -> TcM TcType
- zonkTcTypes :: [TcType] -> TcM [TcType]
- zonkCo :: Coercion -> TcM Coercion
- zonkTyCoVarKind :: TyCoVar -> TcM TyCoVar
- zonkTcTypeMapper :: TyCoMapper () TcM
- zonkEvVar :: EvVar -> TcM EvVar
- zonkWC :: WantedConstraints -> TcM WantedConstraints
- zonkSimples :: Cts -> TcM Cts
- zonkId :: TcId -> TcM TcId
- zonkCoVar :: CoVar -> TcM CoVar
- zonkCt :: Ct -> TcM Ct
- zonkSkolemInfo :: SkolemInfo -> TcM SkolemInfo
- tcGetGlobalTyCoVars :: TcM TcTyVarSet
- ensureNotLevPoly :: Type -> SDoc -> TcM ()
- checkForLevPoly :: SDoc -> Type -> TcM ()
- checkForLevPolyX :: Monad m => (SDoc -> m ()) -> SDoc -> Type -> m ()
- formatLevPolyErr :: Type -> SDoc
Documentation
type TcThetaType = ThetaType Source #
type TcTyVarSet = TyVarSet Source #
newOpenFlexiTyVarTy :: TcM TcType Source #
Create a tyvar that can be a lifted or unlifted type. Returns alpha :: TYPE kappa, where both alpha and kappa are fresh
readMetaTyVar :: TyVar -> TcM MetaDetails Source #
An expected type to check against during type-checking. See Note [ExpType] in TcMType, where you'll also find manipulators.
Constructors
| Check TcType | |
| Infer !InferResult | 
type ExpSigmaType = ExpType Source #
type ExpRhoType = ExpType Source #
newInferExpTypeNoInst :: TcM ExpSigmaType Source #
Make an ExpType suitable for inferring a type of kind * or #.
readExpType_maybe :: ExpType -> TcM (Maybe TcType) Source #
Extract a type out of an ExpType, if one exists. But one should always exist. Unless you're quite sure you know what you're doing.
expTypeToType :: ExpType -> TcM TcType Source #
Extracts the expected type if there is one, or generates a new TauTv if there isn't.
checkingExpType_maybe :: ExpType -> Maybe TcType Source #
Returns the expected type when in checking mode.
checkingExpType :: String -> ExpType -> TcType Source #
Returns the expected type when in checking mode. Panics if in inference mode.
tauifyExpType :: ExpType -> TcM ExpType Source #
Turn a (Infer hole) type into a (Check alpha), where alpha is a fresh unification variable
inferResultToType :: InferResult -> TcM Type Source #
genInstSkolTyVarsX :: SrcSpan -> TCvSubst -> [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar]) Source #
newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence Source #
newWanteds :: CtOrigin -> ThetaType -> TcM [CtEvidence] Source #
cloneWanted :: Ct -> TcM CtEvidence Source #
emitWanted :: CtOrigin -> TcPredType -> TcM EvTerm Source #
Emits a new Wanted. Deals with both equalities and non-equalities.
emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion Source #
Emits a new equality constraint
emitWantedEvVar :: CtOrigin -> TcPredType -> TcM EvVar Source #
Creates a new EvVar and immediately emits it as a Wanted. No equality predicates here.
emitWantedEvVars :: CtOrigin -> [TcPredType] -> TcM [EvVar] Source #
newNoTcEvBinds :: TcM EvBindsVar Source #
Creates an EvBindsVar incapable of holding any bindings. It still tracks covar usages (see comments on ebv_tcvs in TcEvidence), thus must be made monadically
addTcEvBind :: EvBindsVar -> EvBind -> TcM () Source #
fillCoercionHole :: CoercionHole -> Coercion -> TcM () Source #
Put a value in a coercion hole
isFilledCoercionHole :: CoercionHole -> TcM Bool Source #
Is a coercion hole filled in?
unpackCoercionHole :: CoercionHole -> TcM Coercion Source #
Retrieve the contents of a coercion hole. Panics if the hole is unfilled
unpackCoercionHole_maybe :: CoercionHole -> TcM (Maybe Coercion) Source #
Retrieve the contents of a coercion hole, if it is filled
checkCoercionHole :: CoVar -> Coercion -> TcM Coercion Source #
Check that a coercion is appropriate for filling a hole. (The hole itself is needed only for printing. Always returns the checked coercion, but this return value is necessary so that the input coercion is forced only when the output is forced.
tcInstSkolTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar]) Source #
Given a list of [, skolemize the type variables,
 returning a substitution mapping the original tyvars to the
 skolems, and the list of newly bound skolems.  See also
 tcInstSkolTyVars' for a precondition.  The resulting
 skolems are non-overlappable; see Note [Overlap and deriving]
 for an example where this matters.TyVar]
tcSkolDFunType :: DFunId -> TcM ([TcTyVar], TcThetaType, TcType) Source #
instSkolTyCoVarsX :: TcTyCoVarMaker gbl lcl -> TCvSubst -> [TyCoVar] -> TcRnIf gbl lcl (TCvSubst, [TyCoVar]) Source #
freshenTyVarBndrs :: [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TyVar]) Source #
Give fresh uniques to a bunch of TyVars, but they stay as TyVars, rather than becoming TcTyVars Used in FamInst.newFamInst, and Inst.newClsInst
freshenCoVarBndrsX :: TCvSubst -> [CoVar] -> TcRnIf gbl lcl (TCvSubst, [CoVar]) Source #
Give fresh uniques to a bunch of CoVars Used in FamInst.newFamInst
tidySkolemInfo :: TidyEnv -> SkolemInfo -> SkolemInfo Source #
zonkTcTyVarToTyVar :: HasDebugCallStack => TcTyVar -> TcM TcTyVar Source #
zonkTcTypeAndFV :: TcType -> TcM DTyCoVarSet Source #
zonkTcTypeAndSplitDepVars :: TcType -> TcM CandidatesQTvs Source #
Zonk a type and call candidateQTyVarsOfType on it.
quantifyTyVars :: TcTyCoVarSet -> CandidatesQTvs -> TcM [TcTyVar] Source #
zonkCo :: Coercion -> TcM Coercion Source #
Zonk a coercion -- really, just zonk any types in the coercion
zonkTcTypeMapper :: TyCoMapper () TcM Source #
A suitable TyCoMapper for zonking a type during type-checking, before all metavars are filled in.
zonkSkolemInfo :: SkolemInfo -> TcM SkolemInfo Source #
tcGetGlobalTyCoVars :: TcM TcTyVarSet Source #
tcGetGlobalTyCoVars returns a fully-zonked set of *scoped* tyvars free in
 the environment. To improve subsequent calls to the same function it writes
 the zonked set back into the environment. Note that this returns all
 variables free in anything (term-level or type-level) in scope. We thus
 don't have to worry about clashes with things that are not in scope, because
 if they are reachable, then they'll be returned here.
ensureNotLevPoly :: Type -> SDoc -> TcM () Source #
According to the rules around representation polymorphism (see https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds), no binder can have a representation-polymorphic type. This check ensures that we respect this rule. It is a bit regrettable that this error occurs in zonking, after which we should have reported all errors. But it's hard to see where else to do it, because this can be discovered only after all solving is done. And, perhaps most importantly, this isn't really a compositional property of a type system, so it's not a terrible surprise that the check has to go in an awkward spot.
formatLevPolyErr :: Type -> SDoc Source #