
Hi, if I have: data Foobar a b = Foobar it has kind: * -> * -> * How can I force the kind to: (* -> *) -> * -> * ? Thank you!

On 26 July 2016 at 20:36, Michael Roth 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@gmail.com http://IvanMiljenovic.wordpress.com

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
On 26 July 2016 at 20:36, Michael Roth
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@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.
participants (3)
-
Alejandro Serrano Mena
-
Ivan Lazar Miljenovic
-
Michael Roth