Standard Haskell has a rich type language. Types classify terms and serve to
avoid many common programming mistakes. The kind language, however, is
relatively simple, distinguishing only lifted types (kind *
),
type constructors (eg. kind * -> * -> *
), and unlifted
types (Section 7.2.1, “Unboxed types
”). In particular when using advanced
type system features, such as type families (Section 7.7, “Type families”)
or GADTs (Section 7.4.7, “Generalised Algebraic Data Types (GADTs)”), this simple kind system is insufficient,
and fails to prevent simple errors. Consider the example of type-level natural
numbers, and length-indexed vectors:
data Ze data Su n data Vec :: * -> * -> * where Nil :: Vec a Ze Cons :: a -> Vec a n -> Vec a (Su n)
The kind of Vec
is * -> * -> *
. This means
that eg. Vec Int Char
is a well-kinded type, even though this
is not what we intend when defining length-indexed vectors.
With the flags -XPolyKinds
and -XDataKinds
,
users get access to a richer kind language.
-XPolyKinds
enables kind polymorphism, while
-XDataKinds
enables user defined kinds through datatype
promotion. With -XDataKinds
, the example above can then be
rewritten to:
data Nat = Ze | Su Nat data Vec :: * -> Nat -> * where Nil :: Vec a Ze Cons :: a -> Vec a n -> Vec a (Su n)
With the improved kind of Vec
, things like
Vec Int Char
are now ill-kinded, and GHC will report an
error.
In this section we show a few examples of how to make use of the new kind system. This extension is described in more detail in the paper Giving Haskell a Promotion, which appeared at TLDI 2012.
Currently there is a lot of code duplication in the way Typeable is implemented
(Section 7.5.3, “Deriving clause for extra classes (Typeable
, Data
, etc)”):
class Typeable (t :: *) where typeOf :: t -> TypeRep class Typeable1 (t :: * -> *) where typeOf1 :: t a -> TypeRep class Typeable2 (t :: * -> * -> *) where typeOf2 :: t a b -> TypeRep
Kind polymorphism (with -XPolyKinds
)
allows us to merge all these classes into one:
data Proxy t = Proxy class Typeable t where typeOf :: Proxy t -> TypeRep instance Typeable Int where typeOf _ = TypeRep instance Typeable [] where typeOf _ = TypeRep
Note that the datatype Proxy
has kind
forall k. k -> *
(inferred by GHC), and the new
Typeable
class has kind
forall k. k -> Constraint
.
There are some restrictions in the current implementation:
You cannot (yet) explicitly abstract over kinds, or mention kind variables. So the following are all rejected:
data D1 (t :: k) data D2 :: k -> * data D3 (k :: BOX)
The return kind of a type family is always defaulted to
*
. So the following is rejected:
type family F a type instance F Int = Maybe
With -XDataKinds
, GHC automatically promotes every suitable
datatype to be a kind, and its (value) constructors to be type constructors.
The following types
data Nat = Ze | Su Nat data List a = Nil | Cons a (List a) data Pair a b = Pair a b data Sum a b = L a | R b
give rise to the following kinds and type constructors:
Nat :: BOX Ze :: Nat Su :: Nat -> Nat List k :: BOX Nil :: List k Cons :: k -> List k -> List k Pair k1 k2 :: BOX Pair :: k1 -> k2 -> Pair k1 k2 Sum k1 k2 :: BOX L :: k1 -> Sum k1 k2 R :: k2 -> Sum k1 k2
Note that List
, for instance, does not get kind
BOX -> BOX
, because we do not further classify kinds; all
kinds have sort BOX
.
The following restrictions apply to promotion:
We only promote datatypes whose kinds are of the form
* -> ... -> * -> *
. In particular, we do not promote
higher-kinded datatypes such as data Fix f = In (f (Fix f))
,
or datatypes whose kinds involve promoted types such as
Vec :: * -> Nat -> *
.
We do not promote datatypes whose constructors are kind polymorphic, involve constraints, or use existential quantification.
Since constructors and types share the same namespace, with promotion you can get ambiguous type names:
data P -- 1 data Prom = P -- 2 type T = P -- 1 or promoted 2?
In these cases, if you want to refer to the promoted constructor, you should prefix its name with a quote:
type T1 = P -- 1 type T2 = 'P -- promoted 2
Note that promoted datatypes give rise to named kinds. Since these can never be ambiguous, we do not allow quotes in kind names.
Haskell's list and tuple types are natively promoted to kinds, and enjoy the same convenient syntax at the type level, albeit prefixed with a quote:
data HList :: [*] -> * where HNil :: HList '[] HCons :: a -> HList t -> HList (a ': t) data Tuple :: (*,*) -> * where Tuple :: a -> b -> Tuple '(a,b)
Note that this requires -XTypeOperators
.
For the release on GHC 7.4 we focused on getting the new kind-polymorphic core
to work with all existing programs (which do not make use of kind polymorphism).
Many things already work properly with -XPolyKinds
, but we
expect that some things will not work. If you run into trouble, please
report a bug!