[GHC] #14619: Output value of program changes upon compiling with -O optimizations
GHC
ghc-devs at haskell.org
Sat Jan 27 10:05:38 UTC 2018
#14619: Output value of program changes upon compiling with -O optimizations
-------------------------------------+-------------------------------------
Reporter: sheaf | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by AndreasK):
I shrank the repo case a bit:
{{{
module Main where
import Prelude hiding((*>), (<*))
type V3 = (Double, Double, Double)
(<+>) :: V3 -> V3 -> V3
(<+>) (_, _, z) (_, _, z') = (0,0, z+z')
(<.>) :: V3 -> V3 -> Double
(<.>) (x, y, z) (x', y', z') = x*x' +y*y'+z*z'
{-# NOINLINE sphereIntersection #-}
sphereIntersection :: V3 -> V3 -> Maybe (V3, Double)
sphereIntersection orig dir@(_, _, dirz)
| b < 0 = Nothing
| t1 > 0 = Just (dir, dirz)
| t1 < 0 = Just (orig, dirz)
| otherwise = Nothing
where b = orig <.> dir
sqrtDisc = sqrt b
t1 = b - sqrtDisc
main = print . fmap fst $ sphereIntersection (0, 0, 200) (0, 0, 1)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14619#comment:31>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list