[Git][ghc/ghc][master] testsuite: Add test for #16514

Marge Bot gitlab at gitlab.haskell.org
Sun Jun 9 22:41:45 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
41bf4045 by Ben Gamari at 2019-06-09T22:41:38Z
testsuite: Add test for #16514

- - - - -


4 changed files:

- + testsuite/tests/rts/T16514.hs
- + testsuite/tests/rts/T16514.stdout
- + testsuite/tests/rts/T16514_c.cpp
- testsuite/tests/rts/all.T


Changes:

=====================================
testsuite/tests/rts/T16514.hs
=====================================
@@ -0,0 +1,18 @@
+-- ensure that the XMM register values are properly preserved across STG
+-- exit/entry. Note that this is very sensitive to code generation.
+
+module Main where
+
+import Control.Monad (when)
+import System.Exit (exitWith, ExitCode(..))
+
+foreign export ccall fn_hs :: IO ()
+
+fn_hs :: IO ()
+fn_hs = return ()
+
+foreign import ccall test  :: IO Int
+
+main :: IO ()
+main = do res <- test
+          when (res /= 0) (exitWith $ ExitFailure res)


=====================================
testsuite/tests/rts/T16514.stdout
=====================================
@@ -0,0 +1,4 @@
+1.414210 1.732050 2.236070 2.828430 3.605550 4.582580
+1.414210 1.732050 2.236070 2.828430 3.605550 4.582580
+1.414210 1.732050 2.236070 2.828430 3.605550 4.582580
+


=====================================
testsuite/tests/rts/T16514_c.cpp
=====================================
@@ -0,0 +1,45 @@
+#include <iostream>
+#include <stdexcept>
+
+extern "C" {
+
+void fn_hs();
+void fn() {
+    fn_hs();
+}
+
+void check(double sqrt2, double sqrt3,  double sqrt5,
+           double sqrt8, double sqrt13, double sqrt21) {
+    std::cout << std::fixed << sqrt2 << " " << sqrt3 << " " << sqrt5 << " "
+              << sqrt8 << " " << sqrt13 << " " << sqrt21 << std::endl;
+    if (sqrt2 != 1.41421 || sqrt3  != 1.73205 || sqrt5  != 2.23607 ||
+        sqrt8 != 2.82843 || sqrt13 != 3.60555 || sqrt21 != 4.58258) {
+        throw std::runtime_error("xmm registers have been scratched");
+    }
+}
+
+int test() {
+    try {
+        double sqrt2  = 1.41421;
+        double sqrt3  = 1.73205;
+        double sqrt5  = 2.23607;
+        double sqrt8  = 2.82843;
+        double sqrt13 = 3.60555;
+        double sqrt21 = 4.58258;
+        check(sqrt2, sqrt3, sqrt5, sqrt8, sqrt13, sqrt21);
+        fn();
+        check(sqrt2, sqrt3, sqrt5, sqrt8, sqrt13, sqrt21);
+        try {
+            fn();
+        } catch (const std::exception &) {
+        }
+        check(sqrt2, sqrt3, sqrt5, sqrt8, sqrt13, sqrt21);
+    } catch (const std::exception &e) {
+        std::cerr << e.what() << std::endl;
+        return 1;
+    }
+    return 0;
+}
+
+} // extern "C"
+


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -390,3 +390,4 @@ test('keep-cafs',
   ],
   makefile_test, ['KeepCafs'])
 
+test('T16514', unless(opsys('mingw32'), skip), compile_and_run, ['T16514_c.cpp -lstdc++'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/41bf4045c5a85651db8ceb631a1b67edec0c1216

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/41bf4045c5a85651db8ceb631a1b67edec0c1216
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190609/e756a0f0/attachment-0001.html>


More information about the ghc-commits mailing list