[GHC] #11485: Very unhelpful message resulting from kind mismatch
GHC
ghc-devs at haskell.org
Sun Jan 24 04:26:50 UTC 2016
#11485: Very unhelpful message resulting from kind mismatch
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Other
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code:
{{{#!hs
module Foo where
import Data.Typeable
tyConOf :: Typeable a => Proxy a -> TyCon
tyConOf = typeRepTyCon . typeRep
tcList :: TyCon
tcList = tyConOf (Proxy :: Proxy [])
}}}
fails because `-XPolyKinds` is not enabled. But the error message that you
get is quite different on GHC 7.10 and 8.0.
On GHC 7.10.3:
{{{
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Foo.hs:9:19:
Couldn't match kind ‘* -> *’ with ‘*’
Expected type: Proxy a0
Actual type: Proxy []
In the first argument of ‘tyConOf’, namely ‘(Proxy :: Proxy [])’
In the expression: tyConOf (Proxy :: Proxy [])
In an equation for ‘tcList’: tcList = tyConOf (Proxy :: Proxy [])
}}}
But on GHC 8.0.1-rc1:
{{{
Foo.hs:9:19: error:
• Expected kind ‘Proxy []’,
but ‘Data.Proxy.Proxy :: Proxy []’ has kind ‘Proxy []’
• In the first argument of ‘tyConOf’, namely ‘(Proxy :: Proxy [])’
In the expression: tyConOf (Proxy :: Proxy [])
In an equation for ‘tcList’: tcList = tyConOf (Proxy :: Proxy [])
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11485>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list