[commit: ghc] master: Add T12520 as a test (89facad)
git at git.haskell.org
git at git.haskell.org
Tue Aug 23 06:53:42 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/89facad267ff79f1f20b4866428693f423c2d0cc/ghc
>---------------------------------------------------------------
commit 89facad267ff79f1f20b4866428693f423c2d0cc
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date: Tue Aug 23 06:53:11 2016 +0000
Add T12520 as a test
#12520 was already fixed in HEAD. Adding a test to make sure it stays fixed.
>---------------------------------------------------------------
89facad267ff79f1f20b4866428693f423c2d0cc
testsuite/tests/ghci/scripts/T12520.hs | 14 ++++++++++++++
testsuite/tests/ghci/scripts/T12520.script | 2 ++
.../ghci/{prog012/prog012.stdout => scripts/T12520.stdout} | 0
testsuite/tests/ghci/scripts/all.T | 1 +
4 files changed, 17 insertions(+)
diff --git a/testsuite/tests/ghci/scripts/T12520.hs b/testsuite/tests/ghci/scripts/T12520.hs
new file mode 100644
index 0000000..cedf587
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T12520.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+
+module Bug ( box, wrap, proxy ) where
+
+import GHC.Prim
+
+box :: (# Proxy# a, b #) -> b
+box (# x, y #) = y
+
+wrap :: b -> Proxy# a -> (# Proxy# a, b #)
+wrap x = \i# -> (# i#, x #)
+
+proxy :: () -> Proxy# a
+proxy () = proxy#
diff --git a/testsuite/tests/ghci/scripts/T12520.script b/testsuite/tests/ghci/scripts/T12520.script
new file mode 100644
index 0000000..6d6b683
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T12520.script
@@ -0,0 +1,2 @@
+:load T12520
+box (wrap "foo" (proxy ()))
diff --git a/testsuite/tests/ghci/prog012/prog012.stdout b/testsuite/tests/ghci/scripts/T12520.stdout
similarity index 100%
copy from testsuite/tests/ghci/prog012/prog012.stdout
copy to testsuite/tests/ghci/scripts/T12520.stdout
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index 303fd39..70422dc 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -258,3 +258,4 @@ test('T11376', normal, ghci_script, ['T11376.script'])
test('T12007', normal, ghci_script, ['T12007.script'])
test('T11975', normal, ghci_script, ['T11975.script'])
test('T10963', normal, ghci_script, ['T10963.script'])
+test('T12520', normal, ghci_script, ['T12520.script'])
More information about the ghc-commits
mailing list