Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Kind = Type
- typeKind :: Type -> Kind
- isLiftedTypeKind :: Kind -> Bool
- isUnliftedTypeKind :: Kind -> Bool
- isConstraintKind :: Kind -> Bool
- isTYPEApp :: Kind -> Maybe DataCon
- returnsTyCon :: Unique -> Type -> Bool
- returnsConstraintKind :: Kind -> Bool
- isConstraintKindCon :: TyCon -> Bool
- okArrowArgKind :: Kind -> Bool
- okArrowResultKind :: Kind -> Bool
- classifiesTypeWithValues :: Kind -> Bool
- isStarKind :: Kind -> Bool
- isStarKindSynonymTyCon :: TyCon -> Bool
- tcIsStarKind :: Kind -> Bool
- isKindLevPoly :: Kind -> Bool
Main data type
Predicates on Kinds
isLiftedTypeKind :: Kind -> Bool Source #
This version considers Constraint to be distinct from *. Returns True if the argument is equivalent to Type and False otherwise.
isUnliftedTypeKind :: Kind -> Bool Source #
Returns True if the kind classifies unlifted types and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
isConstraintKind :: Kind -> Bool Source #
returnsTyCon :: Unique -> Type -> Bool Source #
Does the given type "end" in the given tycon? For example k -> [a] -> *
ends in *
and Maybe a -> [a]
ends in []
.
returnsConstraintKind :: Kind -> Bool Source #
isConstraintKindCon :: TyCon -> Bool Source #
okArrowArgKind :: Kind -> Bool Source #
okArrowResultKind :: Kind -> Bool Source #
classifiesTypeWithValues :: Kind -> Bool Source #
Does this classify a type allowed to have values? Responds True to things like *, #, TYPE Lifted, TYPE v, Constraint.
True of any sub-kind of OpenTypeKind
isStarKind :: Kind -> Bool Source #
Is this kind equivalent to *?
isStarKindSynonymTyCon :: TyCon -> Bool Source #
Is the tycon Constraint
?
tcIsStarKind :: Kind -> Bool Source #
Is this kind equivalent to *?
isKindLevPoly :: Kind -> Bool Source #
Tests whether the given kind (which should look like TYPE x
)
is something other than a constructor tree (that is, constructors at every node).