Known problems with promoted tuples and lists in GHC 7.4.1?
David Menendez
dave at zednenem.com
Thu Jun 7 00:50:11 CEST 2012
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 <jpm at cs.uu.nl> 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 <dave at zednenem.com> 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 <dave at zednenem.com>
>> <http://www.eyrie.org/~zednenem/>
>>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
--
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>
More information about the Glasgow-haskell-users
mailing list