[commit: testsuite] master: Add a test for #7835 (10ec154)
Ian Lynagh
igloo at ghc.haskell.org
Tue Jul 30 23:31:24 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/10ec15478cbb05a694999a838d993f07e63c1b68
>---------------------------------------------------------------
commit 10ec15478cbb05a694999a838d993f07e63c1b68
Author: Ian Lynagh <ian at well-typed.com>
Date: Tue Jul 30 22:11:31 2013 +0100
Add a test for #7835
>---------------------------------------------------------------
tests/driver/T7835/Makefile | 9 +++++++++
tests/driver/T7835/T7835.stdout | 1 +
tests/driver/T7835/Test.hs | 4 ++++
tests/driver/T7835/TestPrim.hs | 17 +++++++++++++++++
tests/driver/T7835/all.T | 7 +++++++
tests/driver/T7835/test-prims.cmm | 10 ++++++++++
6 files changed, 48 insertions(+)
diff --git a/tests/driver/T7835/Makefile b/tests/driver/T7835/Makefile
new file mode 100644
index 0000000..0248556
--- /dev/null
+++ b/tests/driver/T7835/Makefile
@@ -0,0 +1,9 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T7835:
+ $(RM) Test Test.exe Test.hi Test.o TestPrim.hi TestPrim.o test-prims.o
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 --make Test test-prims.cmm
+ ./Test
+
diff --git a/tests/driver/T7835/T7835.stdout b/tests/driver/T7835/T7835.stdout
new file mode 100644
index 0000000..98d9bcb
--- /dev/null
+++ b/tests/driver/T7835/T7835.stdout
@@ -0,0 +1 @@
+17
diff --git a/tests/driver/T7835/Test.hs b/tests/driver/T7835/Test.hs
new file mode 100644
index 0000000..8b7f141
--- /dev/null
+++ b/tests/driver/T7835/Test.hs
@@ -0,0 +1,4 @@
+import qualified TestPrim
+
+main = print $ TestPrim.tpo 8 9
+
diff --git a/tests/driver/T7835/TestPrim.hs b/tests/driver/T7835/TestPrim.hs
new file mode 100644
index 0000000..f32e7bc
--- /dev/null
+++ b/tests/driver/T7835/TestPrim.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+
+module TestPrim
+ (
+ tpo#
+ , tpo
+ ) where
+
+import GHC.Base -- Int and I#
+
+foreign import prim "test_prim_op" tpo# :: Int# -> Int# -> Int#
+
+tpo :: Int -> Int -> Int
+tpo (I# a) (I# b) = I# (tpo# a b)
diff --git a/tests/driver/T7835/all.T b/tests/driver/T7835/all.T
new file mode 100644
index 0000000..3722f3a
--- /dev/null
+++ b/tests/driver/T7835/all.T
@@ -0,0 +1,7 @@
+
+test('T7835',
+ extra_clean(['Test', 'Test.exe', 'Test.hi', 'Test.o',
+ 'TestPrim.hi', 'TestPrim.o', 'test-prims.o']),
+ run_command,
+ ['$MAKE -s --no-print-directory T7835'])
+
diff --git a/tests/driver/T7835/test-prims.cmm b/tests/driver/T7835/test-prims.cmm
new file mode 100644
index 0000000..fb0a400
--- /dev/null
+++ b/tests/driver/T7835/test-prims.cmm
@@ -0,0 +1,10 @@
+#include "Cmm.h"
+
+test_prim_op (W_ int1, W_ int2)
+{
+ W_ r;
+
+ r = int1 + int2;
+
+ return (r);
+}
More information about the ghc-commits
mailing list