[commit: testsuite] master: Test Trac #8383 (4b16eaa)

git at git.haskell.org git
Fri Oct 4 18:17:10 UTC 2013


Repository : ssh://git at git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/4b16eaa10cf0e42700d9559b462d7d61c11b86c3/testsuite

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

commit 4b16eaa10cf0e42700d9559b462d7d61c11b86c3
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Oct 4 18:51:25 2013 +0100

    Test Trac #8383


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

4b16eaa10cf0e42700d9559b462d7d61c11b86c3
 tests/ghci/scripts/T8383.hs                                    |    8 ++++++++
 tests/ghci/scripts/T8383.script                                |    3 +++
 .../should_run/cgrun056.stdout => ghci/scripts/T8383.stdout}   |    0
 tests/ghci/scripts/all.T                                       |    2 ++
 4 files changed, 13 insertions(+)

diff --git a/tests/ghci/scripts/T8383.hs b/tests/ghci/scripts/T8383.hs
new file mode 100644
index 0000000..44ef0fe
--- /dev/null
+++ b/tests/ghci/scripts/T8383.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE MagicHash #-}
+module T8383 where
+import GHC.Exts
+f :: Int# -> Int#
+f x = x
+foo = print $ (tagToEnum# (f 0#) :: Bool)
+bar = print $ (tagToEnum# (f 1#) :: Bool)
+
diff --git a/tests/ghci/scripts/T8383.script b/tests/ghci/scripts/T8383.script
new file mode 100644
index 0000000..5d43f29
--- /dev/null
+++ b/tests/ghci/scripts/T8383.script
@@ -0,0 +1,3 @@
+:l T8383
+foo
+bar
diff --git a/tests/codeGen/should_run/cgrun056.stdout b/tests/ghci/scripts/T8383.stdout
similarity index 100%
copy from tests/codeGen/should_run/cgrun056.stdout
copy to tests/ghci/scripts/T8383.stdout
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index d5b9e2c..9a278ef 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -156,3 +156,5 @@ test('T8113', normal, ghci_script, ['T8113.script'])
 test('T8172', normal, ghci_script, ['T8172.script'])
 test('T8215', normal, ghci_script, ['T8215.script'])
 test('T8357', normal, ghci_script, ['T8357.script'])
+test('T8383', normal, ghci_script, ['T8383.script'])
+




More information about the ghc-commits mailing list