[GHC] #15067: When Typeable and unboxed sums collide, GHC panics

GHC ghc-devs at haskell.org
Fri Apr 20 00:15:27 UTC 2018


#15067: When Typeable and unboxed sums collide, GHC panics
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.2.2
           Keywords:  Typeable,      |  Operating System:  Unknown/Multiple
  UnboxedSums                        |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This program is enough to send GHC into a tizzy:

 {{{#!hs
 {-# LANGUAGE UnboxedSums #-}
 module Bug1 where

 import Type.Reflection

 floopadoop :: TypeRep (# Bool | Int #)
 floopadoop = typeRep
 }}}
 {{{
 $ ghc Bug.hs
 [1 of 1] Compiling Bug1             ( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.1 for x86_64-unknown-linux):
         tyConRep
   (#|#)
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/deSugar/DsBinds.hs:1314:5 in
 ghc:DsBinds
 }}}

 If you use an unboxed sum data constructor, you can get a different panic:

 {{{#!hs
 {-# LANGUAGE PartialTypeSignatures #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeInType #-}
 {-# LANGUAGE UnboxedSums #-}
 module Bug2 where

 import Language.Haskell.TH
 import Type.Reflection

 type Fweemp = $(conT (unboxedSumDataName 1 2))

 doopafloop :: _ => TypeRep Fweemp
 doopafloop = typeRep
 }}}
 {{{
 $ ghc Bug2.hs
 [1 of 1] Compiling Bug2             ( Bug2.hs, Bug2.o )
 GHC error in desugarer lookup in Bug2:
   Can't find interface-file declaration for variable $tc'(#_|#)
     Probable cause: bug in .hi-boot file, or inconsistent .hi file
     Use -ddump-if-trace to get an idea of which file caused the error
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.1 for x86_64-unknown-linux):
         initDs
 }}}

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


More information about the ghc-tickets mailing list