[commit: testsuite] master: Add test for T7575. (53c7085)

David Terei davidterei at gmail.com
Wed Jan 23 08:05:20 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/53c7085ea1549532ffda281fa13b1569791f3fd6

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

commit 53c7085ea1549532ffda281fa13b1569791f3fd6
Author: David Terei <davidterei at gmail.com>
Date:   Tue Jan 22 23:02:36 2013 -0800

    Add test for T7575.

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

 tests/llvm/should_compile/T7575.hs |   16 ++++++++++++++++
 tests/llvm/should_compile/all.T    |    1 +
 2 files changed, 17 insertions(+), 0 deletions(-)

diff --git a/tests/llvm/should_compile/T7575.hs b/tests/llvm/should_compile/T7575.hs
new file mode 100644
index 0000000..78b0bd2
--- /dev/null
+++ b/tests/llvm/should_compile/T7575.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE MagicHash, UnliftedFFITypes #-}
+module T7575 where
+
+import GHC.Prim
+import GHC.Word
+import GHC.Types
+
+foreign import ccall unsafe "hs_eqWord64" dummy_eqWord64# :: Word64# -> Word64# -> Bool
+
+check :: Word64 -> Word64 -> Bool
+check (W64# x#) (W64# y#) = dummy_eqWord64# x# y#
+
+check2 :: Word64 -> Bool
+check2 x = check x 0
+
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index d0ce873..b2d09ce 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -11,3 +11,4 @@ test('5486', normal, compile, [''])
 test('5681', normal, compile, [''])
 test('6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
 test('T7571', cmm_src, compile, [''])
+test('T7575', normal, compile, [''])





More information about the ghc-commits mailing list