
#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