[GHC] #14754: -O1 changes result at runtime
GHC
ghc-devs at haskell.org
Sat Feb 3 17:43:43 UTC 2018
#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
More information about the ghc-tickets
mailing list