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

#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

#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 (Type | Version: 8.4.1 checker) | Keywords: Typeable, Resolution: | UnboxedSums Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * failure: None/Unknown => Compile-time crash or panic * version: 8.2.2 => 8.4.1 * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15067#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.4.1 checker) | Keywords: Typeable, Resolution: | UnboxedSums Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13276 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13276 Comment: Ah, #13276 claims that unboxed sums shouldn't be `Typeable` at all. I'm fine with this, but it would be nice to have a proper error message in the event one tries to do this instead of panicking. (The commit which established this limitation, 42ff5d97b486d50b0d10e474f47e86822bb71ace, didn't add any regression tests, which might explain why these infelicities went unnoticed.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15067#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15067: When Typeable and unboxed sums collide, GHC panics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Keywords: Typeable, Resolution: | UnboxedSums Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13276 | Differential Rev(s): Phab:D4622, Wiki Page: | Phab:D4623 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D4622, Phab:D4623 Comment: Whoops! See Phab:D4622 and Phab:D4623. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15067#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15067: When Typeable and unboxed sums collide, GHC panics
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.4.1
checker) | Keywords: Typeable,
Resolution: | UnboxedSums
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #13276 | Differential Rev(s): Phab:D4622,
Wiki Page: | Phab:D4623
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15067: When Typeable and unboxed sums collide, GHC panics
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.4.1
checker) | Keywords: Typeable,
Resolution: | UnboxedSums
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #13276 | Differential Rev(s): Phab:D4622,
Wiki Page: | Phab:D4623
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15067: When Typeable and unboxed sums collide, GHC panics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Keywords: Typeable, Resolution: fixed | UnboxedSums Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_fail/T15067 Blocked By: | Blocking: Related Tickets: #13276 | Differential Rev(s): Phab:D4622, Wiki Page: | Phab:D4623 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => typecheck/should_fail/T15067 * status: patch => closed * resolution: => fixed Comment: Thanks, Ben! #13276 tracks the remaining issue of making unboxed sum type/data constructors `Typeable`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15067#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC