[commit: ghc] master: Test case for RULE map coerce = coerce (377672a)

git at git.haskell.org git at git.haskell.org
Tue Feb 11 15:40:32 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/377672ae068f6dbfa0354dfab95f41bdd26b0df4/ghc

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

commit 377672ae068f6dbfa0354dfab95f41bdd26b0df4
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.)


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

377672ae068f6dbfa0354dfab95f41bdd26b0df4
 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..55f7ebb
--- /dev/null
+++ b/testsuite/tests/simplCore/should_run/T2110.stdout
@@ -0,0 +1,3 @@
+yes
+yes
+yes
diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T
index 430d61f..6f5751e 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', expect_broken(2110), 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