Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type TcTyVar = TyVar
- 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
- newMetaKindVar :: TcM TcKind
- newMetaKindVars :: Int -> TcM [TcKind]
- cloneMetaTyVar :: TcTyVar -> TcM TcTyVar
- newFmvTyVar :: TcType -> TcM TcTyVar
- newFskTyVar :: TcType -> TcM TcTyVar
- readMetaTyVar :: TyVar -> TcM MetaDetails
- writeMetaTyVar :: TcTyVar -> TcType -> TcM ()
- writeMetaTyVarRef :: TcTyVar -> TcRef MetaDetails -> TcType -> TcM ()
- newMetaDetails :: MetaInfo -> TcM TcTyVarDetails
- isFilledMetaTyVar :: TyVar -> TcM Bool
- isUnfilledMetaTyVar :: TyVar -> TcM Bool
- data ExpType
- type ExpSigmaType = ExpType
- type ExpRhoType = ExpType
- mkCheckExpType :: TcType -> ExpType
- newOpenInferExpType :: TcM ExpType
- readExpType :: ExpType -> TcM TcType
- readExpType_maybe :: ExpType -> TcM (Maybe TcType)
- writeExpType :: ExpType -> TcType -> TcM ()
- expTypeToType :: ExpType -> TcM TcType
- checkingExpType_maybe :: ExpType -> Maybe TcType
- checkingExpType :: String -> ExpType -> TcType
- tauifyExpType :: ExpType -> TcM ExpType
- 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]
- 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
- addTcEvBind :: EvBindsVar -> EvBind -> TcM ()
- newCoercionHole :: TcM CoercionHole
- fillCoercionHole :: CoercionHole -> Coercion -> TcM ()
- isFilledCoercionHole :: CoercionHole -> TcM Bool
- unpackCoercionHole :: CoercionHole -> TcM Coercion
- unpackCoercionHole_maybe :: CoercionHole -> TcM (Maybe Coercion)
- checkCoercionHole :: Coercion -> CoercionHole -> Role -> Type -> Type -> TcM Coercion
- newMetaTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- newMetaTyVarX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar)
- newMetaSigTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- newSigTyVar :: Name -> Kind -> TcM TcTyVar
- tcInstType :: ([TyVar] -> TcM (TCvSubst, [TcTyVar])) -> TcType -> TcM ([TcTyVar], TcThetaType, TcType)
- tcInstSkolTyVars :: [TyVar] -> TcM (TCvSubst, [TcTyVar])
- tcInstSkolTyVarsLoc :: SrcSpan -> [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar])
- tcInstSuperSkolTyVarsX :: TCvSubst -> [TyVar] -> TcM (TCvSubst, [TcTyVar])
- tcInstSigTyVarsLoc :: SrcSpan -> [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar])
- tcInstSigTyVars :: [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar])
- tcInstSkolType :: TcType -> TcM ([TcTyVar], TcThetaType, TcType)
- tcSkolDFunType :: Type -> TcM ([TcTyVar], TcThetaType, TcType)
- tcSuperSkolTyVars :: [TyVar] -> (TCvSubst, [TcTyVar])
- instSkolTyCoVars :: (Unique -> Name -> Kind -> TyCoVar) -> [TyVar] -> 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)
- zonkTidyOrigin :: TidyEnv -> CtOrigin -> TcM (TidyEnv, CtOrigin)
- mkTypeErrorThing :: TcType -> ErrorThing
- mkTypeErrorThingArgs :: TcType -> Int -> ErrorThing
- tidyEvVar :: TidyEnv -> EvVar -> EvVar
- tidyCt :: TidyEnv -> Ct -> Ct
- tidySkolemInfo :: TidyEnv -> SkolemInfo -> SkolemInfo
- skolemiseUnboundMetaTyVar :: TcTyVar -> TcTyVarDetails -> TcM TyVar
- zonkTcTyVar :: TcTyVar -> TcM TcType
- zonkTcTyVars :: [TcTyVar] -> TcM [TcType]
- zonkTyCoVarsAndFV :: TyCoVarSet -> TcM TyCoVarSet
- zonkTcTypeAndFV :: TcType -> TcM TyCoVarSet
- zonkTcTypeAndSplitDepVars :: TcType -> TcM (Pair TyCoVarSet)
- zonkTcTypesAndSplitDepVars :: [TcType] -> TcM (Pair TyCoVarSet)
- zonkQuantifiedTyVar :: TcTyVar -> TcM (Maybe TcTyVar)
- zonkQuantifiedTyVarOrType :: TcTyVar -> TcM (Either TcTyVar TcType)
- quantifyTyVars :: TcTyCoVarSet -> Pair TcTyCoVarSet -> TcM [TcTyVar]
- quantifyZonkedTyVars :: TcTyCoVarSet -> Pair TcTyCoVarSet -> TcM [TcTyVar]
- defaultKindVar :: TcTyVar -> TcM Kind
- zonkTcTyCoVarBndr :: TcTyCoVar -> TcM TcTyCoVar
- zonkTcTyBinder :: TcTyBinder -> TcM TcTyBinder
- 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
- zonkCt :: Ct -> TcM Ct
- zonkSkolemInfo :: SkolemInfo -> TcM SkolemInfo
- tcGetGlobalTyCoVars :: TcM TcTyVarSet
Documentation
type TcThetaType = ThetaType Source #
type TcTyVarSet = TyVarSet Source #
newOpenFlexiTyVarTy :: TcM TcType Source #
Create a tyvar that can be a lifted or unlifted type.
readMetaTyVar :: TyVar -> TcM MetaDetails Source #
writeMetaTyVarRef :: TcTyVar -> TcRef MetaDetails -> TcType -> TcM () Source #
An expected type to check against during type-checking. See Note [ExpType] in TcMType, where you'll also find manipulators.
type ExpSigmaType = ExpType Source #
type ExpRhoType = ExpType Source #
newOpenInferExpType :: TcM ExpType 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 unificaiton variable
genInstSkolTyVarsX :: SrcSpan -> TCvSubst -> [TyVar] -> TcRnIf gbl lcl (TCvSubst, [TcTyVar]) Source #
newWanted :: CtOrigin -> Maybe TypeOrKind -> PredType -> TcM CtEvidence Source #
newWanteds :: CtOrigin -> ThetaType -> 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 #
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 :: Coercion -> CoercionHole -> Role -> Type -> Type -> TcM Coercion Source #
Check that a coercion is appropriate for filling a hole. (The hole itself is needed only for printing. NB: This must be lazy in the coercion, as it's used in TcHsSyn in the presence of knots. Always returns the checked coercion, but this return value is necessary so that the input coercion is forced only when the output is forced.
tcInstSkolType :: TcType -> TcM ([TcTyVar], TcThetaType, TcType) Source #
tcSkolDFunType :: Type -> TcM ([TcTyVar], TcThetaType, TcType) Source #
instSkolTyCoVars :: (Unique -> Name -> Kind -> TyCoVar) -> [TyVar] -> 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
mkTypeErrorThing :: TcType -> ErrorThing Source #
Make an ErrorThing
storing a type.
mkTypeErrorThingArgs :: TcType -> Int -> ErrorThing Source #
Make an ErrorThing
storing a type, with some extra args known about
tidySkolemInfo :: TidyEnv -> SkolemInfo -> SkolemInfo Source #
zonkTcTypeAndFV :: TcType -> TcM TyCoVarSet Source #
zonkTcTypeAndSplitDepVars :: TcType -> TcM (Pair TyCoVarSet) Source #
Zonk a type and call splitDepVarsOfType
on it.
Works within the knot.
zonkTcTypesAndSplitDepVars :: [TcType] -> TcM (Pair TyCoVarSet) Source #
zonkQuantifiedTyVarOrType :: TcTyVar -> TcM (Either TcTyVar TcType) Source #
Like zonkQuantifiedTyVar, but if zonking reveals that the tyvar should become a type (when defaulting a RuntimeRep var to PtrRepLifted), it returns the type instead.
quantifyTyVars :: TcTyCoVarSet -> Pair TcTyCoVarSet -> TcM [TcTyVar] Source #
quantifyZonkedTyVars :: TcTyCoVarSet -> Pair TcTyCoVarSet -> TcM [TcTyVar] Source #
defaultKindVar :: TcTyVar -> TcM Kind Source #
Take an (unconstrained) meta tyvar and default it. Works only on vars of type RuntimeRep and of type *. For other kinds, it issues an error. See Note [Defaulting with -XNoPolyKinds]
zonkTcTyBinder :: TcTyBinder -> TcM TcTyBinder Source #
Zonk a TyBinder
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 inside the knot, and 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.