[GHC] #14619: Output value of program changes upon compiling with -O optimizations

GHC ghc-devs at haskell.org
Sat Dec 30 10:09:23 UTC 2017


#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 Phyx-):

 I'm starting to think this isn't a GHC bug. I've attached two dumps
 created with the current `HEAD` and `8.2.2`. Because the representation of
 `show` for `Float` seems to have changed I'm avoiding using it.

 My repro is

 {{{
 module Main where

 import Prelude hiding((*>), (<*))

 type V3 = (Double, Double, Double)

 infixl 6 <+>
 infixl 7 <.>
 infix  8 *>

 (<+>) :: V3 -> V3 -> V3
 (<+>) (x, y, z) (x', y', z') = (x+x', y+y', z+z')
 (*>) :: Double -> V3 -> V3
 (*>)  a         (x', y', z') = (a*x', a*y', a*z')
 (<.>) :: V3 -> V3 -> Double
 (<.>) (x, y, z) (x', y', z') = x*x'+y*y'+z*z'

 sphereIntersection :: V3 -> V3 -> V3 -> Maybe (V3, Double)
 sphereIntersection orig dir@(_, _, dirz) c
   | b < 0  = Nothing
   | t1   > 0  = Just (t1 *> dir, dirz)
   | t2   > 0  = Just (t2 *> orig, dirz)
   | otherwise = Nothing
     where oc = c <+> orig
           b  = oc <.> dir
           sqrtDisc = sqrt b
           t1 = b - sqrtDisc
           t2 = b + sqrtDisc

 result = sphereIntersection (0, 0, 0) (0, 0, 1) (0, 0, 200)

 main :: IO (Maybe (V3, Double))
 main = return result
 }}}

 Both are compiled with `-fforce-recomp -O2 -ddump-cmm -ddump-to-file` and
 there is no meaningful difference in code gen. only label names. The only
 remaining difference is in toolchain. 8.4.1 has an upgraded toolchain (and
 so head) vs 8.2.2. So this is looking like an upstream issue.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14619#comment:19>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list