[GHC] #15203: Wrong location reported for kind error

GHC ghc-devs at haskell.org
Thu May 31 03:30:21 UTC 2018


#15203: Wrong location reported for kind error
-------------------------------------+-------------------------------------
           Reporter:  goldfire       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.5
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When I try to compile

 {{{#!hs
 {-# LANGUAGE PolyKinds, ConstraintKinds, TypeFamilies, FlexibleContexts
 #-}

 module Bug where

 import Data.Proxy

 type T (a :: k1) (b :: k2) = (a ~ b, Show (Proxy (a :: k1)), Show (Proxy
 (b :: k2)))
 }}}

 I get

 {{{
 Bug.hs:7:80: error:
     • Couldn't match ‘k1’ with ‘k2’
     • In the type declaration for ‘T’
   |
 7 | type T (a :: k1) (b :: k2) = (a ~ b, Show (Proxy (a :: k1)), Show
 (Proxy (b :: k2)))
   |
 ^^
 }}}

 The problem is that the `k2` that's highlighted has nothing at all to do
 with the error. Indeed, some experimentation shows that GHC will highlight
 the first occurrence of `k2` to the right of the `=`. The error is
 actually from unification caused by `a ~ b`.

 I noticed this because I've been tightening up the way GHC does left-to-
 right ordering during implicit quantification (while working on something
 more substantial). In so doing, I made sure to prefer kind variable
 occurrences to the ''left'' of the = over those to the right. But then I
 got a testsuite failure due to a changed location of an error.

 This is caused by the call to `report_sig_tv_err` in `tcTyClTyVars`.

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


More information about the ghc-tickets mailing list