[GHC] #8616: "Internal error" with ScopedTypeVariables and kind variables

GHC ghc-devs at haskell.org
Mon Dec 16 19:27:08 UTC 2013


#8616: "Internal error" with ScopedTypeVariables and kind variables
------------------------------------+-------------------------------------
       Reporter:  goldfire          |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.7
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 When I try to compile the following nonsense with HEAD

 {{{
 {-# LANGUAGE PolyKinds, RankNTypes, ScopedTypeVariables #-}

 import Data.Proxy
 import GHC.Exts

 withSomeSing :: forall (kproxy :: k). Proxy kproxy
 withSomeSing = undefined :: (Any :: k)
 }}}

 I get this

 {{{
     GHC internal error: ‛k’ is not in scope during type checking, but it
 passed the renamer
     tcl_env of environment: [(a4XG, Type variable ‛kproxy’ = kproxy),
                              (r4MW,
                               Identifier[withSomeSing::forall (k :: BOX)
 (kproxy :: k).
                                                        Proxy k kproxy,
 <NotTopLevel>])]
     In the kind ‛k’
     In an expression type signature: (Any :: k)
     In the expression: undefined :: (Any :: k)
 }}}

 The code is very bogus, but so is GHC's response.

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


More information about the ghc-tickets mailing list