
#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