[GHC] #13819: GHC Panics

#13819: GHC Panics -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE DeriveFunctor, TypeApplications #-} -- {-# Language ViewPatterns #-} -- {-# Language InstanceSigs, ViewPatterns, TupleSections, GeneralizedNewtypeDeriving, TemplateHaskell, LambdaCase #-} module D where import Data.Coerce import Control.Applicative newtype A a = A (IO a) deriving Functor instance Applicative A where pure = pure @(_ -> WrappedMonad A _) @(_ -> A _) pure instance Monad A where }}} causes a panic {{{ $ ghci -ignore-dot-ghci /tmp/a.hs GHCi, version 8.3.20170605: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling D ( /tmp/a.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170605 for x86_64-unknown-linux): repSplitAppTys w0_a1xc[tau:4] WrappedMonad A w0_a1xe[tau:4] [] 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/types/Type.hs:809:9 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: GHC Panics -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * version: 8.0.1 => 8.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications 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): * component: Compiler => Compiler (Type checker) * priority: normal => high * failure: None/Unknown => Compile-time crash or panic * version: 8.3 => 8.2.1-rc2 * milestone: => 8.2.1 * keywords: => TypeApplications Comment: Yikes, this is a regression from GHC 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications 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 simonpj): * cc: goldfire (added) Comment: Richard, this is yet more fallout from the terrible `uo_thing` mess. The panic comes from the argument-counting in `repSplitAppTys`, when called from `mkTypErrorThing` or `mkTypeErrorThingArgs`. At the moment we construct this `ErrorThing` the kind of the type has not been zonked, so we have a `FunTy t1 t2` with `t1 :: kappa`. I guess this will be fixed when we tidy up `uo_thing`... but that is looking increasingly urgent. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications 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): * cc: bgamari (added) Comment: FWIW, commit b207b536ded40156f9adb168565ca78e1eef2c74 (`Generalize kind of the (->) tycon`) is what introduced this regression. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications 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: | -------------------------------------+------------------------------------- Comment (by simonpj): See also #13846 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13846, #13850 Comment: Two more ways to trigger this panic: * #13846: {{{ $ ghci -XTypeApplications -ignore-dot-ghci GHCi, version 8.3.20170605: http://www.haskell.org/ghc/ :? for help Prelude> :t fmap @(_ -> _) ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170605 for x86_64-unknown-linux): repSplitAppTys w0_a1pF[tau:2] w0_a1pH[tau:2] [] 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/types/Type.hs:809:9 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} * #13850 {{{
cat wibble.hs ecase :: Either a b -> (a -> c) (b -> c) -> c ecase (Left a) f _ = f a ecase (Right b) _ g = g b
ghci wibble.hs GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/erikd/.ghci [1 of 1] Compiling Main ( wibble.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): repSplitAppTys a_a1pA[sk:1] c_a1pC[sk:1] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:808:9 in ghc:Type }}}
Both of these were also caused by b207b536ded40156f9adb168565ca78e1eef2c74. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): My start toward fixing this is at https://github.com/goldfirere/ghc/tree /uo-thing but I'm about to go on holiday. I may have time to finish while traveling, but no guarantees. If someone wants to carry this over the line, I'd be grateful. Otherwise, back in full action on July 5. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Just for the record, I'm back on this. Will have a fix soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Any update on this, goldfire? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => goldfire -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * differential: => Phab:D3754 Comment: As it turns out, yes! All fixed on my end. Right now, I have a raft of bugfixes that just need to get validated and such. This is one of them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: I'm afraid we're going to have to punt on this for 8.2.1. The patch is simply too large to merge this late in the game (especially since backports tend to be extra painful with the trees-that-grow change behind us). Perhaps we can make this happen for 8.2.2 if someone yells, but otherwise I would be tempted to simply wait for 8.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: goldfire
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords:
Resolution: | TypeApplications
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: merge Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_fail/T13819 Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_fail/T13819 * status: patch => merge Comment: This patch isn't tiny, but it seems worthwhile to merge. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: merge Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_fail/T13819 Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ben, I take it that commit c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 (`Fix #13819 by refactoring TypeEqOrigin.uo_thing`) isn't going to be merged into 8.2.2? If so, we ought to close this. It's interesting to note that even though that commit hasn't been merged to 8.2.2, the program in this ticket not longer panics on GHC 8.2.2! It turns out that commit cbf472384b5b583c24d1a1a32f3fa58d4f1501b1 (`Small refactor of getRuntimeRep`) //separately// fixed this panic, and that commit was backported to 8.2.2. So that's nice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_fail/T13819 Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Phab:D3754 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Indeed I think it's out of the running for 8.2.2 and, given its size, perhaps out of scope for 8.2 on the whole. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13819#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC