[Haskell-cafe] Forcing the kind in data

Alejandro Serrano Mena trupill at gmail.com
Tue Jul 26 10:59:37 UTC 2016


Given that neither `a` nor `b` are used in the data type, you could also
make `Foobar` kind-polymorphic:

{-# LANGUAGE PolyKinds #-}
data Foobar a b = Foobar

You can check that GHC has inferred polymorphic kinds by asking for
information in a GHCi prompt:

Prelude> :info Foobar
data Foobar (a :: k1) (b :: k2) = Foobar

2016-07-26 12:55 GMT+02:00 Ivan Lazar Miljenovic <ivan.miljenovic at gmail.com>
:

> On 26 July 2016 at 20:36, Michael Roth <list at mroth.net> wrote:
> > Hi,
> >
> > if I have:
> >
> >     data Foobar a b = Foobar
> >
> > it has kind:
> >
> >     * -> * -> *
> >
> > How can I force the kind to:
> >
> >      (* -> *) -> * -> *
>
> {-# LANGUAGE KindSignatures #-}
>
> data Foobar (a :: * -> *) (b :: *) = Foobar
>
> --
> Ivan Lazar Miljenovic
> Ivan.Miljenovic at gmail.com
> http://IvanMiljenovic.wordpress.com
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160726/cf04ac2a/attachment.html>


More information about the Haskell-Cafe mailing list