[GHC] #8084: Enabling PolyKinds makes some type errors weird

GHC ghc-devs at haskell.org
Mon Jul 22 22:56:05 CEST 2013


#8084: Enabling PolyKinds makes some type errors weird
-------------------------------------------+-------------------------------
       Reporter:  MartijnVanSteenbergen    |             Owner:
           Type:  bug                      |            Status:  new
       Priority:  normal                   |         Milestone:
      Component:  Compiler (Type checker)  |           Version:  7.6.3
       Keywords:                           |  Operating System:
   Architecture:  Unknown/Multiple         |  Unknown/Multiple
     Difficulty:  Unknown                  |   Type of failure:
     Blocked By:                           |  None/Unknown
Related Tickets:                           |         Test Case:
                                           |          Blocking:
-------------------------------------------+-------------------------------
 Consider this program:

 {{{
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE PolyKinds #-}

 module Existential where

 data Any (f :: k -> *)

 data X a
 data Y (a :: *)
 data Z (a :: Bool)

 x :: Any X -> ()
 x 'c' = ()

 y :: Any Y -> ()
 y 'c' = ()

 z :: Any Z -> ()
 z 'c' = ()
 }}}

 x, y and z are all ill-typed, but the shapes of the type errors are
 different in each case. They are respectively:

 {{{
     Couldn't match expected type `Any k (X k)' with actual type `Char'
     Couldn't match expected type `Any * Y' with actual type `Char'
     Couldn't match expected type `Any Bool Z' with actual type `Char'
 }}}

 Aren't they supposed to say just 'Any X', 'Any Y' and 'Any Z'?

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8084>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler




More information about the ghc-tickets mailing list