[GHC] #15436: Compile-time panic, Prelude.!!: negative index

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | 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: -------------------------------------+------------------------------------- Here is a reproduction case: **ghc-repro.cabal** {{{ name: ghc-repro version: 0.0.0 build-type: Simple cabal-version: >= 1.10 library exposed-modules: Lib other-modules: Paths_ghc_repro hs-source-dirs: src build-depends: base default-language: Haskell2010 }}} **src/Lib.hs** {{{#!hs {-# OPTIONS_GHC -v4 #-} module Lib where import GHC.Enum -- | At this many elements, it panics. One fewer, it works data USState = AL | AK | AZ | AR | CA | CO | CT | DE | FL -- | GA -- | HI | ID | IL | IN | IA | KS | KY | LA | ME | MD -- | MA | MI | MN | MS | MO | MT | NE | NV | NH | NJ -- | NM | NY | NC | ND | OH | OK | OR | PA | RI | SC -- | SD | TN | TX | UT | VT | VA | WA | WV | WI | WY -- | DC | PR | VI | AS | GU | MP | AA | AE | AP deriving (Eq, Show, Ord, Bounded, Read, Enum) data USStateOrIntl = International | US USState instance Enum USStateOrIntl where fromEnum International = 0 fromEnum (US s) = 1 + fromEnum s enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen toEnum 0 = International toEnum i = US . toEnum $ i - 1 instance Bounded USStateOrIntl where minBound = International maxBound = US maxBound }}} **Results**: {{{ ghc-repro-0.0.0: build (lib) Preprocessing library for ghc-repro-0.0.0.. Building library for ghc-repro-0.0.0.. Running phase HsPp HsSrcFile compile: input file src/Lib.hs *** Checking old interface for ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib (use -ddump-hi-diffs for more details): [1 of 2] Compiling Lib ( src/Lib.hs, .stack- work/dist/x86_64-linux/Cabal-2.2.0.1/build/Lib.o ) *** Parser [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: !!! Parser [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 8.31 milliseconds, allocated 17.533 megabytes *** Renamer/typechecker [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: !!! Renamer/typechecker [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 354.49 milliseconds, allocated 312.556 megabytes *** Desugar [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: Result size of Desugar (after optimization) = {terms: 752, types: 352, coercions: 33, joins: 1/4} !!! Desugar [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 142.79 milliseconds, allocated 226.278 megabytes *** Simplifier [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: Result size of Simplifier iteration=1 = {terms: 1,222, types: 790, coercions: 143, joins: 1/3} Result size of Simplifier iteration=2 = {terms: 1,219, types: 788, coercions: 126, joins: 0/1} Result size of Simplifier = {terms: 1,217, types: 786, coercions: 123, joins: 0/1} !!! Simplifier [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 374.08 milliseconds, allocated 587.256 megabytes *** Specialise [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: Result size of Specialise = {terms: 1,217, types: 786, coercions: 123, joins: 0/1} !!! Specialise [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 154.05 milliseconds, allocated 235.323 megabytes *** Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) [ghc- repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) = {terms: 1,551, types: 1,410, coercions: 123, joins: 0/0} !!! Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) [ghc- repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: finished in 6.24 milliseconds, allocated 5.556 megabytes *** Simplifier [ghc-repro-0.0.0-K1NxTAQg5MjG2d3fZc1tOj:Lib]: Result size of Simplifier iteration=1 = {terms: 1,667, types: 1,082, coercions: 123, joins: 7/19} ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-unknown-linux): Prelude.!!: negative index Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The above output was produced through my normal tooling, so {{{ stack build --resolver lts-12.2 --pedantic }}} To rule out stack, I was also able to reproduce the panic with plain cabal using this **Dockerfile**: {{{ FROM haskell:8.4.3 RUN mkdir /src WORKDIR /src COPY ghc-repro.cabal /src/ghc-repo.cabal COPY src/Lib.hs /src/src/Lib.hs RUN cabal build }}} {{{ docker build --tag ghc-repro . }}} It still panics, but the output is different and much larger so I'll leave it here: https://8n1.org/13499/5c92 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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 osa1): * version: 8.4.3 => 8.5 Comment: Confirmed on GHC HEAD. To reproduce without cabal just do `ghc-stage2 Lib.hs -O`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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 osa1): The failing `!!` call is this (in PrelRules.hs): {{{ get_con :: Type -> ConTagZ -> DataCon get_con ty tag = tyConDataCons (tyConAppTyCon ty) !! tag }}} Which is passed a negative tag in this call site probably (same file): {{{ tx_con_dtt ty (LitAlt (LitNumber LitNumInt i _)) = DataAlt (get_con ty (fromInteger i)) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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 hsyl20): `-fno-case-folding` makes the panic disappear -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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: simonpj (added) Comment: This was probably caused by commit 193664d42dbceadaa1e4689dfa17ff1cf5a405a0 (`Re-engineer caseRules to add tagToEnum/dataToTag`), considering that this panic does not occur on GHC 8.2 or earlier (see also #14680). simonpj, do you know what is happening here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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 hsyl20): Given this simpler code: {{{#!hs module Bug0 where import GHC.Enum data XXX = AL | AK | AZ | AR | CA | CO | CT | DE | FL deriving (Enum) data Z = Y | X XXX instance Enum Z where fromEnum (X s) = 1 + fromEnum s --fromEnum Y = 0 toEnum 0 = Y --toEnum i = X . toEnum $ i - 1 }}} We have the following sequence of transformations for `succ`: {{{#!hs toEnumZ :: Int -> Z toEnumZ 0 = Y toEnumZ x = ... fromEnumZ :: Z -> Int fromEnumZ Y = ... fromEnumZ (X x) = 1 + fromEnumX x succZ :: Z -> Z succZ = toEnumZ . (+1) . fromEnumZ ===> {inline toEnumZ} succZ z = case (fromEnumZ z) + 1 of 0 -> Y x -> ... ===> {case-folding} succZ z = case fromEnumZ z of -1 -> Y x -> ... }}} We could stop here: `fromEnumZ` is basically `dataToTag#` and we have a negative literal alternative. If we continue: {{{#!hs ===> {inline fromEnumZ} succZ z = case (case z of Y -> 0 (X x) -> 1 + fromEnumX x) of -1 -> Y x -> ... ===> {case-of-case} succZ z = case z of Y -> ... X x -> case 1 + fromEnumX x of -1 -> Y s -> ... }}} And this is what we get: {{{#!hs $csucc_a2vu :: Z -> Z $csucc_a2vu = \ (x_a2Km :: Z) -> case x_a2Km of { Y -> case lvl_s2RN of wild_00 { }; X s_aED -> case s_aED of x1_a2IA { __DEFAULT -> case GHC.Prim.dataToTag# @ XXX x1_a2IA of a#_aI4 { __DEFAULT -> case GHC.Prim.+# 1# a#_aI4 of lwild_s2St { __DEFAULT -> lvl_s2R2; -1# -> Bug0.Y } } } } }}} When we have fewer data constructors for XXX, `fromEnumX` is inlined as a case so there is no `dataToTag#` involved: {{{#!hs $csucc_a2vh :: Z -> Z $csucc_a2vh = \ (x_a2K7 :: Z) -> case x_a2K7 of { Y -> case lvl_s2Ry of wild_00 { }; X s_aEC -> join { $j_s2Sa :: GHC.Prim.Int# -> Z [LclId[JoinId(1)], Arity=1] $j_s2Sa (x1_a2Ka [OS=OneShot] :: GHC.Prim.Int#) = case x1_a2Ka of lwild_s2S9 { __DEFAULT -> lvl_s2QN; -1# -> Bug0.Y } } in case s_aEC of { AL -> jump $j_s2Sa 1#; AK -> jump $j_s2Sa 2#; AZ -> jump $j_s2Sa 3#; AR -> jump $j_s2Sa 4#; CA -> jump $j_s2Sa 5#; CO -> jump $j_s2Sa 6#; CT -> jump $j_s2Sa 7#; DE -> jump $j_s2Sa 8# } } }}} Perhaps we could simply discard negative literal alternatives when we match on `dataToTag#`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: 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): Phab:D5008 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch * differential: => Phab:D5008 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index
-------------------------------------+-------------------------------------
Reporter: pbrisbin | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
Resolution: | Keywords:
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): Phab:D5008
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_run/T15436 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5008 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: patch => merge * testcase: => simplCore/should_run/T15436 Comment: OK, done! Thanks hsyl20. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_run/T15436 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5008 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 851f3341953587d9fd2e471994b37ad81f132b1a. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_run/T15436 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5008 Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): I was just about to finally file this bug I ran into back in May already w/ GHC 8.4.2 but didn't have time to investigate and instead workarounded via https://github.com/text-utf8/text- utf8/commit/5ba8f5d1d4c0f39399d8c32f069e4132c92ef099 It'd be great to have this fixed in GHC 8.4.4 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15436: Compile-time panic, Prelude.!!: negative index -------------------------------------+------------------------------------- Reporter: pbrisbin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_run/T15436 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5008 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.4.4 Comment: This was merged to `ghc-8.4` in 66c75922e04355ab3babc9c76eab6c97ddceec1e. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15436#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC