
#15696: Derived Ord instance for enumerations with more than 8 elements seems to be incorrect -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.2 Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Weirdly enough, I get different answers than the ones simonpj reported for the program in comment:13. To be explicit, if I'm using this program: {{{#!hs {-# LANGUAGE MagicHash #-} module Main where import GHC.Exts (dataToTag#, tagToEnum#, (==#), (<#)) main :: IO () main = print $ compare a T2 where {-# NOINLINE f #-} f = T2 {-# NOINLINE a #-} a = f data T = T1 | T2 | T3 | T4 | T5 | T6 | T7 | T8 | T9 deriving (Eq, Show) instance Ord Main.T where compare a b = case dataToTag# a of a' -> case dataToTag# b of b' -> if tagToEnum# (a' <# b') :: Bool then LT else if tagToEnum# (a' ==# b') :: Bool then EQ else GT }}} Then I consistently get `LT` regardless of optimization level: {{{ $ /opt/ghc/8.6.1/bin/ghc -O0 -fforce-recomp Bug.hs && ./Bug [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... LT $ /opt/ghc/8.6.1/bin/ghc -O2 -fforce-recomp Bug.hs && ./Bug [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... LT }}} If I replace all uses of `dataToTag#` with `getTag`, however: {{{#!hs {-# LANGUAGE MagicHash #-} module Main where import GHC.Base (getTag) import GHC.Exts (tagToEnum#, (==#), (<#)) main :: IO () main = print $ compare a T2 where {-# NOINLINE f #-} f = T2 {-# NOINLINE a #-} a = f data T = T1 | T2 | T3 | T4 | T5 | T6 | T7 | T8 | T9 deriving (Eq, Show) instance Ord Main.T where compare a b = case getTag a of a' -> case getTag b of b' -> if tagToEnum# (a' <# b') :: Bool then LT else if tagToEnum# (a' ==# b') :: Bool then EQ else GT }}} Only then do I get `EQ` without optimization: {{{ $ /opt/ghc/8.6.1/bin/ghc -O0 -fforce-recomp Bug.hs && ./Bug [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... EQ $ /opt/ghc/8.6.1/bin/ghc -O2 -fforce-recomp Bug.hs && ./Bug [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... LT }}} What's more, I consistently get the same sets of results in each version of GHC dating back to 8.2.2. This makes me believe that the bug that was exposed here has actually been lurking for quite a while (but perhaps a difference in inlining behavior in 8.6 only just recently exposed it). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15696#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler