Known problems with promoted tuples and lists in GHC 7.4.1?

Are there any known issues involving type-level pairs and lists? I've
hit a few baffling type errors that went away when I refactored my
code to use locally-defined pairs and lists instead of those provided
by the prelude.
More worryingly, I had one function that would stop passing the type
checker if I replaced '[n] with (n ': '[]) in its signature.
--
Dave Menendez

Hi David,
Are you using HEAD? If so, and you run into problems, please report them
(either here or as bugs in trac).
Thanks,
Pedro
On Wed, Jun 6, 2012 at 9:37 PM, David Menendez
Are there any known issues involving type-level pairs and lists? I've hit a few baffling type errors that went away when I refactored my code to use locally-defined pairs and lists instead of those provided by the prelude.
More worryingly, I had one function that would stop passing the type checker if I replaced '[n] with (n ': '[]) in its signature.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

No, I'm just running 7.4.1.
Here's a very stripped-down example of what I'm seeing:
{-# LANGUAGE PolyKinds, DataKinds #-}
data Pair a b = P a b
data Nat = Z | S Nat
data Phantom i = Phantom
okay :: Phantom ('P Int Int)
okay = Phantom
-- not_okay :: Phantom '(Int, Int)
-- not_okay = Phantom
Uncommenting that last bit results in this error,
Couldn't match kind `BOX' against `*'
Kind incompatibility when matching types:
k0 :: BOX
(*, *) :: *
In the expression: Phantom
In an equation for `not_okay': not_okay = Phantom
Something seems to have gone wrong internally.
On Wed, Jun 6, 2012 at 5:43 PM, José Pedro Magalhães
Hi David,
Are you using HEAD? If so, and you run into problems, please report them (either here or as bugs in trac).
Thanks, Pedro
On Wed, Jun 6, 2012 at 9:37 PM, David Menendez
wrote: Are there any known issues involving type-level pairs and lists? I've hit a few baffling type errors that went away when I refactored my code to use locally-defined pairs and lists instead of those provided by the prelude.
More worryingly, I had one function that would stop passing the type checker if I replaced '[n] with (n ': '[]) in its signature.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--
Dave Menendez

Kind polymorphism and promoted kinds is *not* an advertised feature of 7.4.1. Much code is there, but it doesn't work when you push it. The HEAD does work. If you are using kind polymorphism or promoted kinds, use HEAD (or a development snapshot).
Indeed not_okay compiles fine with HEAD
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-
| users-bounces@haskell.org] On Behalf Of David Menendez
| Sent: 06 June 2012 23:50
| To: José Pedro Magalhães
| Cc: glasgow-haskell-users@haskell.org Mailing List
| Subject: Re: Known problems with promoted tuples and lists in GHC 7.4.1?
|
| No, I'm just running 7.4.1.
|
| Here's a very stripped-down example of what I'm seeing:
|
| {-# LANGUAGE PolyKinds, DataKinds #-}
|
| data Pair a b = P a b
| data Nat = Z | S Nat
|
| data Phantom i = Phantom
|
| okay :: Phantom ('P Int Int)
| okay = Phantom
|
| -- not_okay :: Phantom '(Int, Int)
| -- not_okay = Phantom
|
| Uncommenting that last bit results in this error,
|
| Couldn't match kind `BOX' against `*'
| Kind incompatibility when matching types:
| k0 :: BOX
| (*, *) :: *
| In the expression: Phantom
| In an equation for `not_okay': not_okay = Phantom
|
| Something seems to have gone wrong internally.
|
|
| On Wed, Jun 6, 2012 at 5:43 PM, José Pedro Magalhães

On Thu, Jun 7, 2012 at 2:37 AM, Simon Peyton-Jones
Kind polymorphism and promoted kinds is *not* an advertised feature of 7.4.1. Much code is there, but it doesn't work when you push it. The HEAD does work. If you are using kind polymorphism or promoted kinds, use HEAD (or a development snapshot).
I'll keep that in mind if I do anything serious. For now, I've been able to work around the oddity by using my own pairs and lists. If anything, it works better than I expected.
Indeed not_okay compiles fine with HEAD
Glad to hear it.
| -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of David Menendez | Sent: 06 June 2012 23:50 | To: José Pedro Magalhães | Cc: glasgow-haskell-users@haskell.org Mailing List | Subject: Re: Known problems with promoted tuples and lists in GHC 7.4.1? | | No, I'm just running 7.4.1. | | Here's a very stripped-down example of what I'm seeing: | | {-# LANGUAGE PolyKinds, DataKinds #-} | | data Pair a b = P a b | data Nat = Z | S Nat | | data Phantom i = Phantom | | okay :: Phantom ('P Int Int) | okay = Phantom | | -- not_okay :: Phantom '(Int, Int) | -- not_okay = Phantom | | Uncommenting that last bit results in this error, | | Couldn't match kind `BOX' against `*' | Kind incompatibility when matching types: | k0 :: BOX | (*, *) :: * | In the expression: Phantom | In an equation for `not_okay': not_okay = Phantom | | Something seems to have gone wrong internally. | | | On Wed, Jun 6, 2012 at 5:43 PM, José Pedro Magalhães
| wrote: | > Hi David, | > | > Are you using HEAD? If so, and you run into problems, please report | > them (either here or as bugs in trac). | > | > | > Thanks, | > Pedro | > | > On Wed, Jun 6, 2012 at 9:37 PM, David Menendez | wrote: | >> | >> Are there any known issues involving type-level pairs and lists? I've | >> hit a few baffling type errors that went away when I refactored my | >> code to use locally-defined pairs and lists instead of those provided | >> by the prelude. | >> | >> More worryingly, I had one function that would stop passing the type | >> checker if I replaced '[n] with (n ': '[]) in its signature. | >> | >> -- | >> Dave Menendez | >> http://www.eyrie.org/~zednenem/ | >> | >> _______________________________________________ | >> Glasgow-haskell-users mailing list | >> Glasgow-haskell-users@haskell.org | >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users | > | > | | | | -- | Dave Menendez | http://www.eyrie.org/~zednenem/ | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--
Dave Menendez
participants (3)
-
David Menendez
-
José Pedro Magalhães
-
Simon Peyton-Jones