Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1be5e53cf3c511ac7cbf316514680b539f716692

>---------------------------------------------------------------

commit 1be5e53cf3c511ac7cbf316514680b539f716692
Author: Simon Marlow <[email protected]>
Date:   Fri Jan 13 11:09:24 2012 +0000

    Expand num009 to test more values, and add mingw32 output
    
    This test checks that calling trig functions via the FFI gives the
    same results as the Prelude versions.  But it uses an extreme value to
    test: 1e20, and on Windows this gives slightly different results (for
    unknown reasons).  However, using less extreme values gives reasonable
    results, so I've added more values to the test to check that the
    discrepancy is limited to the extreme - indeed it first goes wrong
    around 1e19, values below that seem to be fine.

>---------------------------------------------------------------

 tests/Numeric/all.T                              |   10 +++++++++-
 tests/Numeric/num009.hs                          |   18 +++++++++---------
 tests/Numeric/num009.stdout-i386-unknown-mingw32 |   16 ++++++++++++++++
 3 files changed, 34 insertions(+), 10 deletions(-)

diff --git a/tests/Numeric/all.T b/tests/Numeric/all.T
index d6237fb..b4218b3 100644
--- a/tests/Numeric/all.T
+++ b/tests/Numeric/all.T
@@ -6,5 +6,13 @@ test('num005', normal, compile_and_run, [''])
 test('num006', normal, compile_and_run, [''])
 test('num007', normal, compile_and_run, [''])
 test('num008', normal, compile_and_run, [''])
-test('num009', compose(skip_if_fast, if_os('darwin', expect_broken(2370))), 
compile_and_run, [''])
+test('num009', [ skip_if_fast
+               , if_os('darwin', expect_broken(2370))
+               , if_os('mingw32', omit_ways(['ghci'])) ],
+               # We get different results at 1e20 on x86/Windows, so there is
+               # a special output file for that.  I (SDM) don't think these are
+               # serious, since the results for lower numbers are all fine.
+               # We also get another set of results for 1e02 with GHCi, so
+               # I'm skipping that way altogether.
+             compile_and_run, [''])
 test('num010', normal, compile_and_run, [''])
diff --git a/tests/Numeric/num009.hs b/tests/Numeric/num009.hs
index 58ab586..a49f318 100644
--- a/tests/Numeric/num009.hs
+++ b/tests/Numeric/num009.hs
@@ -7,14 +7,14 @@ module Main(main) where
 import Control.Monad
 import Foreign.C
 
-main = do let d = 1e20 :: Double
-              f = 1e20 :: Float
-          test "sind" sind sin d
-          test "sinf" sinf sin f
-          test "cosd" cosd cos d
-          test "cosf" cosf cos f
-          test "tand" tand tan d
-          test "tanf" tanf tan f
+main = do let d = [0, pi, pi/2, pi/3, 1e10, 1e20] :: [Double]
+              f = [0, pi, pi/2, pi/3, 1e10, 1e20] :: [Float]
+          mapM_ (test "sind" sind sin) d
+          mapM_ (test "sinf" sinf sin) f
+          mapM_ (test "cosd" cosd cos) d
+          mapM_ (test "cosf" cosf cos) f
+          mapM_ (test "tand" tand tan) d
+          mapM_ (test "tanf" tanf tan) f
           putStrLn "Done"
 
 test :: (RealFloat a, Floating a, RealFloat b, Floating b, Show b)
@@ -22,7 +22,7 @@ test :: (RealFloat a, Floating a, RealFloat b, Floating b, 
Show b)
 test s f g x = do let y = realToFrac (f (realToFrac x))
                       z = g x
                   unless (y == z) $ do
-                      putStrLn s
+                      putStrLn (s ++ ' ':show x)
                       print y
                       print z
                       print $ decodeFloat y
diff --git a/tests/Numeric/num009.stdout-i386-unknown-mingw32 
b/tests/Numeric/num009.stdout-i386-unknown-mingw32
new file mode 100644
index 0000000..d01a5a1
--- /dev/null
+++ b/tests/Numeric/num009.stdout-i386-unknown-mingw32
@@ -0,0 +1,16 @@
+sind 1.0e20
+-0.7304509250633894
+-0.7469218912594929
+(-6579317027855829,-53)
+(-6727674302302237,-53)
+cosd 1.0e20
+-0.6829651865754496
+-0.6649117899070088
+(-6151603519536432,-53)
+(-5988992978518909,-53)
+tand 1.0e20
+1.0695287833425957
+1.123339821307656
+(4816729430123734,-52)
+(5059072800651599,-52)
+Done



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to