[GHC] #14754: -O1 changes result at runtime

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.1-alpha1 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: -------------------------------------+------------------------------------- I found a program, which works as expected in GHC 8.4.1-alpha1 with `-O0`, but freezes with `-O1`. {{{ module Main where import Debug.Trace main :: IO () main = print (alg 3 1) alg :: Word -> Word -> Word alg a b | traceShow (a, b) False = undefined | c < b = alg b c | c > b = alg c b | otherwise = c where c = a - b }}} {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.0.20180118 $ ghc -O0 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) Linking alg ... $ ./alg (3,1) (2,1) 1 $ ghc -O1 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) [Optimisation flags changed] Linking alg ... $ ./alg 2>&1 | head (3,1) (1,2) (2,18446744073709551615) (18446744073709551615,3) ^C }}} For some reason an optimised program chooses a wrong case at the very first invocation of `alg`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.1-alpha1 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 mpickering): Which operating system are you using? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.1-alpha1 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 Bodigrim): macOS High Sierra 10.13.3 I encountered the issue, because it affects build of `arithmoi` on Travis, so it should be reproducible on Ubuntu too. GHC 8.2.2 is fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 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 * milestone: => 8.4.1 Old description:
I found a program, which works as expected in GHC 8.4.1-alpha1 with `-O0`, but freezes with `-O1`.
{{{ module Main where
import Debug.Trace
main :: IO () main = print (alg 3 1)
alg :: Word -> Word -> Word alg a b | traceShow (a, b) False = undefined | c < b = alg b c | c > b = alg c b | otherwise = c where c = a - b }}}
{{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.0.20180118 $ ghc -O0 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) Linking alg ... $ ./alg (3,1) (2,1) 1 $ ghc -O1 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) [Optimisation flags changed] Linking alg ... $ ./alg 2>&1 | head (3,1) (1,2) (2,18446744073709551615) (18446744073709551615,3) ^C }}}
For some reason an optimised program chooses a wrong case at the very first invocation of `alg`.
New description: I found a program, which works as expected in GHC 8.4.1-alpha1 with `-O0`, but freezes with `-O1`. {{{#!hs module Main where import Debug.Trace main :: IO () main = print (alg 3 1) alg :: Word -> Word -> Word alg a b | traceShow (a, b) False = undefined | c < b = alg b c | c > b = alg c b | otherwise = c where c = a - b }}} {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.0.20180118 $ ghc -O0 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) Linking alg ... $ ./alg (3,1) (2,1) 1 $ ghc -O1 alg.hs [1 of 1] Compiling Main ( alg.hs, alg.o ) [Optimisation flags changed] Linking alg ... $ ./alg 2>&1 | head (3,1) (1,2) (2,18446744073709551615) (18446744073709551615,3) ^C }}} For some reason an optimised program chooses a wrong case at the very first invocation of `alg`. -- Comment: Yikes! Thank you for catching this. I guess this means my plans for another alpha release today are on hold. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 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): This was caused by commit 7920a7d9c53083b234e060a3e72f00b601a46808 (`cmm/CBE: Collapse blocks equivalent up to alpha renaming of local registers`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 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 bgamari): Indeed the problem here is that the CBE logic in the above patch find these two blocks to be equivalent: {{{ c4N2: // global _s4Kg::I64 = _s4Kg::I64; _s4Kf::I64 = _s4Kr::I64; goto c4M3; c4N5: // global _s4Kf::I64 = _s4Kg::I64; _s4Kg::I64 = _s4Kr::I64; goto c4M3; }}} The reason is that the implementation walks the two blocks, zipping together their nodes and building a correspondence between their local registers. In the first node we have {{{ c4N2 c4N5 ---------------- --------------- s4Kg = s4Kg s4Kf = s4Kg }}} As the RHSs of the assignments are identical, this results in the correspondence `s4Kg(c4N2) ~> s4Kf(s4N5)`. We then consider the second pair of nodes: {{{ c4N2 c4N5 ---------------- --------------- s4Kf = s4Kr s4Kg = s4Kr }}} Since the implementation binding occurrences are simply added to the register substitution instead of compared, these two nodes are considered to be equivalent. This is clearly wrong. I'll need to revisit this in the future but in the meantime I'm going to revert. implementation fails to take into account that logic registers may live beyond the -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha1
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

#14754: -O1 changes result at runtime
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha1
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

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14226 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * related: => #14226 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14226 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.4`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14226 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bodigrim): Is this test case run with `-O1` option? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14226 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): In the `optasm` testsuite way, yes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14754: -O1 changes result at runtime -------------------------------------+------------------------------------- Reporter: Bodigrim | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14226 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Wow, fast diagnosis Ryan! Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14754#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC