[commit: ghc] wip/nomeata-T2110: Test case for RULE map coerce = coerce (2ff7f72)
git at git.haskell.org
git at git.haskell.org
Mon Jan 27 10:36:59 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nomeata-T2110
Link : http://ghc.haskell.org/trac/ghc/changeset/2ff7f72a67ff18d344cd4e035be5b690d6c1ca60/ghc
>---------------------------------------------------------------
commit 2ff7f72a67ff18d344cd4e035be5b690d6c1ca60
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Jan 27 10:36:34 2014 +0000
Test case for RULE map coerce = coerce
(This tests #2110.)
>---------------------------------------------------------------
2ff7f72a67ff18d344cd4e035be5b690d6c1ca60
testsuite/tests/simplCore/should_run/T2110.hs | 28 +++++++++++++++++++++
testsuite/tests/simplCore/should_run/T2110.stdout | 3 +++
testsuite/tests/simplCore/should_run/all.T | 1 +
3 files changed, 32 insertions(+)
diff --git a/testsuite/tests/simplCore/should_run/T2110.hs b/testsuite/tests/simplCore/should_run/T2110.hs
new file mode 100644
index 0000000..fb65781
--- /dev/null
+++ b/testsuite/tests/simplCore/should_run/T2110.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE MagicHash #-}
+
+import GHC.Exts
+import Unsafe.Coerce
+
+{-# RULES
+"map/coerce" map coerce = coerce
+ #-}
+
+newtype Age = Age Int
+
+fooAge :: [Int] -> [Age]
+fooAge = map Age
+fooCoerce :: [Int] -> [Age]
+fooCoerce = map coerce
+fooUnsafeCoerce :: [Int] -> [Age]
+fooUnsafeCoerce = map unsafeCoerce
+
+same :: a -> b -> IO ()
+same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of
+ 1# -> putStrLn "yes"
+ _ -> putStrLn "no"
+
+main = do
+ let l = [1,2,3]
+ same (fooAge l) l
+ same (fooCoerce l) l
+ same (fooUnsafeCoerce l) l
diff --git a/testsuite/tests/simplCore/should_run/T2110.stdout b/testsuite/tests/simplCore/should_run/T2110.stdout
new file mode 100644
index 0000000..07d92f5
--- /dev/null
+++ b/testsuite/tests/simplCore/should_run/T2110.stdout
@@ -0,0 +1,3 @@
+yes
+yes
+no
diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T
index 430d61f..fa11dc5 100644
--- a/testsuite/tests/simplCore/should_run/all.T
+++ b/testsuite/tests/simplCore/should_run/all.T
@@ -51,6 +51,7 @@ test('T5453', normal, compile_and_run, [''])
test('T5441', extra_clean(['T5441a.o','T5441a.hi']),
multimod_compile_and_run, ['T5441',''])
test('T5603', normal, compile_and_run, [''])
+test('T2110', normal, compile_and_run, [''])
# Run these tests *without* optimisation too
test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, [''])
More information about the ghc-commits
mailing list