ghc-7.4.2: The GHC API

Safe HaskellNone

Kind

Contents

Synopsis

Main data type

type Kind = TypeSource

The key type representing kinds in the compiler. Invariant: a kind is always in one of these forms:

 FunTy k1 k2
 TyConApp PrimTyCon [...]
 TyVar kv   -- (during inference only)
 ForAll ... -- (for top-level coercions)

anyKind :: KindSource

See Type for details of the distinction between these Kinds

liftedTypeKind :: KindSource

See Type for details of the distinction between these Kinds

unliftedTypeKind :: KindSource

See Type for details of the distinction between these Kinds

openTypeKind :: KindSource

See Type for details of the distinction between these Kinds

argTypeKind :: KindSource

See Type for details of the distinction between these Kinds

ubxTupleKind :: KindSource

See Type for details of the distinction between these Kinds

constraintKind :: KindSource

See Type for details of the distinction between these Kinds

mkArrowKind :: Kind -> Kind -> KindSource

Given two kinds k1 and k2, creates the Kind k1 -> k2

mkArrowKinds :: [Kind] -> Kind -> KindSource

Iterated application of mkArrowKind

anyKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

liftedTypeKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

openTypeKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

unliftedTypeKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

argTypeKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

ubxTupleKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

constraintKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

tySuperKind :: SuperKindSource

tySuperKindTyCon :: TyConSource

See Type for details of the distinction between the Kind TyCons

Deconstructing Kinds

kindFunResult :: Kind -> KindOrType -> KindSource

Essentially funResultTy on kinds handling pi-types too

synTyConResKind :: TyCon -> KindSource

Find the result Kind of a type synonym, after applying it to its arity number of type variables Actually this function works fine on data types too, but they'd always return *, so we never need to ask

splitKindFunTys :: Kind -> ([Kind], Kind)Source

Essentially splitFunTys on kinds

splitKindFunTysN :: Int -> Kind -> ([Kind], Kind)Source

Essentially splitFunTysN on kinds

Predicates on Kinds

isUnliftedTypeKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isOpenTypeKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isUbxTupleKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isArgTypeKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isConstraintKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isConstraintOrLiftedKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isKind :: Kind -> BoolSource

Is this a kind (i.e. a type-of-types)?

isSuperKind :: Type -> BoolSource

Is this a super-kind (i.e. a type-of-kinds)?

isAnyKind :: Kind -> BoolSource

See Type for details of the distinction between these Kinds

isSubArgTypeKind :: Kind -> BoolSource

True of any sub-kind of ArgTypeKind

tcIsSubArgTypeKind :: Kind -> BoolSource

True of any sub-kind of ArgTypeKind

isSubOpenTypeKind :: Kind -> BoolSource

True of any sub-kind of OpenTypeKind

True of any sub-kind of OpenTypeKind

tcIsSubOpenTypeKind :: Kind -> BoolSource

True of any sub-kind of OpenTypeKind

defaultKind :: Kind -> KindSource

Used when generalising: default OpenKind and ArgKind to *. See Type for more information on what that means

isSubKindCon :: TyCon -> TyCon -> BoolSource

kc1 `isSubKindCon` kc2 checks that kc1 <: kc2

Functions on variables

Promotion related functions

promoteType :: Type -> KindSource

Promotes a type to a kind. Assumes the argument is promotable.