[GHC] #14608: Different GHCi error messages for similar scenarios

#14608: Different GHCi error messages for similar scenarios -------------------------------------+------------------------------------- Reporter: mb64 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With the following code: {{{#!hs {-# LANGUAGE UnboxedTuples #-} module Test where data UnboxedTupleData = MkUTD (# (),() #) doThings :: UnboxedTupleData -> () doThings (MkUTD t) = () }}} This is accepted and compiled with a simple `ghc --make Test.hs`. However, with `ghci Test.hs`, you get an ugly error message: {{{#!hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Test ( Test.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): bcIdPrimRep t_s1ro :: (# (), () #) Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/ghci/ByteCodeGen.hs:1582:5 in ghc:ByteCodeGen Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Replacing `(MkUTD t)` with just `t` obtains a different error, with a nicer message: {{{#!hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Test ( Test.hs, interpreted ) Error: bytecode compiler can't handle unboxed tuples and sums. Possibly due to foreign import/export decls in source. Workaround: use -fobject-code, or compile this module to .o separately. }}} True to its word, GHCi accepts it with `-fobject-code`, but it also accepts the unwrapping one, with the worse error message, with `-fobject- code`. It only happens with unboxed tuples in GHCi: if you replace the unboxed tuple with an unboxed int, GHCi will happily accept it. GHC cheerfully compiles everything. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14608 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14608: Different GHCi error messages for similar scenarios -------------------------------------+------------------------------------- Reporter: mb64 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This panic first started appearing in commit 714bebff44076061d0a719c4eda2cfd213b7ac3d (`Implement unboxed sum primitive type`). The panic changed to its current `bcIdPrimRep` form in commit e7985ed23ddc68b6a2e4af753578dc1d9e8ab4c9 (`Update levity polymorphism`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14608#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14608: Different GHCi error messages for similar scenarios -------------------------------------+------------------------------------- Reporter: mb64 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah. I believe the culprit is the fact that these two lines were removed: https://github.com/ghc/ghc/commit/714bebff44076061d0a719c4eda2cfd213b7ac3d #diff-6fd42166fdf8d397ba9081bb24661f1fL851 Previously, this would check that in interpreted code, any alternatives in a pattern match would not scrutinize unboxed tuples. But since that check was removed, it falls through and eventually results in the disastrous panic shown above. Luckily, we should be able to reinstate this check with relative ease. Patch coming soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14608#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14608: Different GHCi error messages for similar scenarios -------------------------------------+------------------------------------- Reporter: mb64 | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4276 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4276 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14608#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14608: Different GHCi error messages for similar scenarios
-------------------------------------+-------------------------------------
Reporter: mb64 | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: GHCi | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Poor/confusing | Unknown/Multiple
error message | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4276
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14608: Different GHCi error messages for similar scenarios -------------------------------------+------------------------------------- Reporter: mb64 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4276 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14608#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC