#4867: Incorrect result from trig functions
-------------------------------+--------------------------------------------
    Reporter:  gwright         |        Owner:  gwright                    
        Type:  bug             |       Status:  new                        
    Priority:  high            |    Milestone:  7.0.2                      
   Component:  GHCi            |      Version:  7.0.1                      
    Keywords:                  |     Testcase:                             
   Blockedby:                  |   Difficulty:                             
          Os:  MacOS X         |     Blocking:                             
Architecture:  x86_64 (amd64)  |      Failure:  Incorrect result at runtime
-------------------------------+--------------------------------------------

Comment(by gwright):

 Replying to [comment:13 simonmar]:
 > Is the bug consistently reproducible, i.e. the same expressions always
 give the same (right or wrong) answers?
 >
 > Do you get any failures in the numeric tests?
 >
 > I would proceed by reducing the example further, e.g. call your own tanh
 and add some traces.

 The same expressions give the same correct or incorrect answers.  For
 example, the result of `tanh(x)` is wrong for `x` negative. For positive
 `x`, the result is correct.

 However, whatever is going on is not whether the argument is positive or
 negative, but whether the result is positive or negative.  For the `cos`
 function,
 {{{
 Prelude> cos(pi/2 - 0.001)
 9.999998333332927e-4
 Prelude> cos(pi/2)
 6.123233995736766e-17
 Prelude> cos(pi/2 + 0.001)
 -5.696722673613253e74
 Prelude>
 }}}
 As the result of the `cos` becomes negative, the result is wrong.

 Hmm.  This gives me an idea --- perhaps the bug is in showing the result.
 Let's try
 {{{
 Prelude> let x = -0.0001
 Prelude> x
 -5.379511282975455e73
 Prelude>
 }}}
 Yes! But compiling
 {{{
 module Main where

 main = do
         let x = -0.001
         print x
 }}}
 and running it gives
 {{{
 plumbbob-franklin> ./foo
 -1.0e-3
 }}}
 the right answer.

 Perhaps the problem is just showing a negative result:
 {{{
 Prelude> let x = -0.0001
 Prelude> let y = 1.2
 Prelude> x * y
 -4.8047181618589074e73
 Prelude> let z = -1.2
 Prelude> x * z
 1.2e-4
 Prelude>
 Prelude> (abs x) * y
 1.2e-4
 Prelude>
 }}}
 So the value of `x` is saved correctly, only when the result of the REPL
 is negative doe we get garbage.

 Well, now I have a better idea of what to look for.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to