[GHC] #9882: Kind mismatch with singleton [Nat]
GHC
ghc-devs at haskell.org
Sat Dec 13 10:21:17 UTC 2014
#9882: Kind mismatch with singleton [Nat]
-------------------------------------+-------------------------------------
Reporter: Roel van Dijk | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Keywords: | Operating System: Linux
Architecture: Unknown/Multiple | Type of failure: GHC
Difficulty: Unknown | rejects valid program
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
import GHC.TypeLits ( Nat )
data Foo (n :: [Nat]) = Foo
x :: Foo ('(:) 42 '[])
x = Foo
y :: Foo (42 ': '[])
y = Foo
z :: Foo [42]
z = Foo
}}}
{{{
Expected kind ‘*’, but ‘42’ has kind ‘Nat’
In the type signature for ‘z’: z :: Foo [42]
}}}
I would expected z to be identical to both x and y. The error occurs in
both GHCi and GHC.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9882>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list