[GHC] #16394: GHC internal error while typechecking of instance definition

GHC ghc-devs at haskell.org
Tue Mar 5 22:17:18 UTC 2019


#16394: GHC internal error while typechecking of instance definition
-------------------------------------+-------------------------------------
           Reporter:  Day1721        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  low            |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
  (Type checker)                     |
           Keywords:                 |  Operating System:  Linux
       Architecture:                 |   Type of failure:  Incorrect
  Unknown/Multiple                   |  error/warning at compile-time
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Hello. \\
 This code won't typecheck because of GHC internal error.

 {{{#!hs
 {-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-}

 class C a where
     type T (n :: a)

 --       v--DIFF--v
 instance C a => C b => C (a, b) where
     type T '(n, m) = (T n, T m)
 }}}

 with error message:
 {{{
 Bug.hs:7:10: error:
     • GHC internal error: ‘T’ is not in scope during type checking, but it
 passed the renamer
       tcl_env of environment: [a1LS :-> Type variable ‘a’ = a :: *,
                                a1LT :-> Type variable ‘b’ = b :: *]
     • In the type instance declaration for ‘T’
       In the instance declaration for ‘C b => C (a, b)’
   |
 7 |     type T (n, m) = (T n, T m)
   |          ^
 Failed, no modules loaded.

 }}}

 but this works fine:
 {{{#!hs
 {-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-}

 class C a where
     type T (n :: a)

 --       v--DIFF--v
 instance (C a, C b) => C (a, b) where
     type T '(n, m) = (T n, T m)
 }}}

 Not sure is a bug, but either way it would be better to make more
 understandable error message

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


More information about the ghc-tickets mailing list