[commit: ghc] master: Test Trac #3990 (251a376)

git at git.haskell.org git at git.haskell.org
Fri Apr 22 10:30:03 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/251a376baf9b3824a67fba3bfb9a72bc31cf8e33/ghc

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

commit 251a376baf9b3824a67fba3bfb9a72bc31cf8e33
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Apr 21 13:29:37 2016 +0100

    Test Trac #3990


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

251a376baf9b3824a67fba3bfb9a72bc31cf8e33
 testsuite/tests/simplCore/should_compile/Makefile     |  5 +++++
 testsuite/tests/simplCore/should_compile/T3990.hs     | 12 ++++++++++++
 testsuite/tests/simplCore/should_compile/T3990.stdout |  2 ++
 testsuite/tests/simplCore/should_compile/all.T        |  4 ++++
 4 files changed, 23 insertions(+)

diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile
index 87b1d95..8b7da66 100644
--- a/testsuite/tests/simplCore/should_compile/Makefile
+++ b/testsuite/tests/simplCore/should_compile/Makefile
@@ -2,6 +2,11 @@ TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
+T3990:
+	$(RM) -f T3990.o T3990.hi
+	'$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T3990.hs | grep 'test_case'
+        # Grep output should show an unpacked constructor
+
 T8832:
 	$(RM) -f T8832.o T8832.hi
 	'$(TEST_HC)' $(TEST_HC_OPTS) $(T8832_WORDSIZE_OPTS) -O -c -ddump-simpl T8832.hs | grep '^[a-zA-Z0-9]\+ ='
diff --git a/testsuite/tests/simplCore/should_compile/T3990.hs b/testsuite/tests/simplCore/should_compile/T3990.hs
new file mode 100644
index 0000000..9877175
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T3990.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TypeFamilies #-}
+module T3990 where
+
+data family Complex a
+data instance Complex Double = CD {-# UNPACK #-} !Double
+                                  {-# UNPACK #-} !Double
+
+data T = T {-# UNPACK #-} !(Complex Double)
+-- This shouuld actually get unpacked!
+
+test_case :: T
+test_case = T (CD 1 1)
diff --git a/testsuite/tests/simplCore/should_compile/T3990.stdout b/testsuite/tests/simplCore/should_compile/T3990.stdout
new file mode 100644
index 0000000..20d0871
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T3990.stdout
@@ -0,0 +1,2 @@
+test_case :: T
+test_case = T3990.T 1.0## 1.0##
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 9f3af8b..7aba485 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -232,3 +232,7 @@ test('T11232', normal, compile, ['-O2'])
 test('T11562', normal, compile, ['-O2'])
 test('T11742', normal, compile, ['-O2'])
 test('T11644', normal, compile, ['-O2'])
+test('T3990',
+     normal,
+     run_command,
+     ['$MAKE -s --no-print-directory T3990'])



More information about the ghc-commits mailing list