[GHC] #14768: -O1 changes result at runtime, duplicating __DEFAULT case

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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: -------------------------------------+------------------------------------- Here is a program, which works as expected in GHC 8.4.1-alpha3 with `-O0`, but changes it behaviour with `-O1`. {{{#!hs {-# LANGUAGE MagicHash #-} import qualified Data.Vector.Unboxed as U import GHC.Exts vec :: U.Vector Moebius vec = U.singleton Moebius0 main :: IO () main = print $ U.head vec == U.head vec data Moebius = Moebius0 | Moebius1 | Moebius2 deriving (Eq) fromMoebius :: Moebius -> Int fromMoebius Moebius0 = 0 fromMoebius Moebius1 = 1 fromMoebius Moebius2 = 2 toMoebius :: Int -> Moebius toMoebius (I# i#) = tagToEnum# i# {- ...unboxed vector instances, see file attached... -} }}} It is expected that this program will print `True`. However, when compiled with `-O1` it prints `False`. {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.0.20180204 $ ghc -O0 Sieve.hs && ./Sieve [1 of 1] Compiling Main ( Sieve.hs, Sieve.o ) [Optimisation flags changed] Linking Sieve ... True $ ghc -O1 Sieve.hs && ./Sieve [1 of 1] Compiling Main ( Sieve.hs, Sieve.o ) [Optimisation flags changed] Linking Sieve ... False }}} It reproduces on OS X and Ubuntu, but worked fine in GHC 8.2. I looked into generated Core and found a suspicious function, having two `__DEFAULT` cases with different bodies. {{{#!hs main2 :: String main2 = case vec `cast` Co:3 of { Vector ipv_sb7L ipv1_sb7M ipv2_sb7N -> case <# 0# ipv1_sb7M of { __DEFAULT -> case main3 ipv1_sb7M of wild_00 { }; 1# -> case indexIntArray# ipv2_sb7N ipv_sb7L of { __DEFAULT -> $fShowBool4; __DEFAULT -> $fShowBool2; 1# -> $fShowBool2; 2# -> $fShowBool2 } } } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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: | -------------------------------------+------------------------------------- Changes (by Bodigrim): * Attachment "Sieve.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => highest Comment: Thank you for reporting this. Indeed this is an interesting case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha3
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 Ben Gamari

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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 simonpj): Could not resist looking at this. I know what is happening. Patch coming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * Attachment "Bug.hs" added. Version without dependencies -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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): In case it's useful, I've attached a variation of `Sieve.hs` without a `vector` dependency. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 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 simonpj): In the test case there is no need to run it. Core Lint picks up the error immediately. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha3
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 Simon Peyton Jones

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | simplCore/should_run/T14768 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => simplCore/should_run/T14768 * status: new => merge Comment: I guess we should merge this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | simplCore/should_run/T14768 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Many thanks to Bodigrim for finding this, with such a tractable test case! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14768: -O1 changes result at runtime, duplicating __DEFAULT case -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | simplCore/should_run/T14768 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as 4e0b4b36aca29b4d67df5f36d1a06bdfdfeec612. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14768#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC