[GHC] #11821: Internal error: not in scope during type checking, but it passed the renamer

GHC ghc-devs at haskell.org
Wed Nov 30 21:01:47 UTC 2016


#11821: Internal error: not in scope during type checking, but it passed the
renamer
-------------------------------------+-------------------------------------
        Reporter:  darchon           |                Owner:
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:  8.0.2
       Component:  Compiler          |              Version:  8.0.1-rc3
      Resolution:  fixed             |             Keywords:  TypeInType
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  GHC rejects       |            Test Case:
  valid program                      |  polykinds/T11821
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):  Phab:D2146
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by int-index):

 I've stumbled on this bug with a smaller example:

 {{{
 {-# LANGUAGE TypeInType, ConstraintKinds #-}
 import Data.Proxy
 type SameKind (a :: k1) (b :: k2) = ('Proxy :: Proxy k1) ~ ('Proxy ::
 Proxy k2)
 }}}

 And the error message with GHC 8.0 is

 {{{
 SameKind.hs:3:77: error:
     • GHC internal error: ‘k2’ is not in scope during type checking, but
 it passed the renamer
       tcl_env of environment: [arZ :-> Type variable ‘k1’ = k1,
                                as0 :-> Type variable ‘a’ = a, as2 :-> Type
 variable ‘b’ = b,
                                rq7 :-> ATcTyCon SameKind]
     • In the first argument of ‘Proxy’, namely ‘k2’
       In the kind ‘Proxy k2’
       In the second argument of ‘~’, namely ‘(Proxy :: Proxy k2)’
 }}}

 The bug is indeed fixed in GHC 8.0.2. I'm posting this because I believe a
 smaller test case would be a valuable addition to the test suite.

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


More information about the ghc-tickets mailing list