Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1c72f4d046dbd5dfa6441d17ac8efa9313260146

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

commit 1c72f4d046dbd5dfa6441d17ac8efa9313260146
Author: Simon Peyton Jones <[email protected]>
Date:   Sat Jun 11 14:42:14 2011 +0100

    Test Trac #5252

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

 tests/ghc-regress/deSugar/should_compile/T5252.hs  |   13 +++++++++++++
 tests/ghc-regress/deSugar/should_compile/T5252a.hs |    5 +++++
 tests/ghc-regress/deSugar/should_compile/all.T     |    4 ++++
 3 files changed, 22 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/deSugar/should_compile/T5252.hs 
b/tests/ghc-regress/deSugar/should_compile/T5252.hs
new file mode 100644
index 0000000..e2498c4
--- /dev/null
+++ b/tests/ghc-regress/deSugar/should_compile/T5252.hs
@@ -0,0 +1,13 @@
+-- Trac #5252
+-- Killed 7.03 when compiled witout -O, 
+-- because it could not see that x had a product type
+-- but MkS still unpacked it
+
+module T5252 where
+import T5252a
+
+blah :: S -> T
+blah (MkS x _) = x
+
+
+
diff --git a/tests/ghc-regress/deSugar/should_compile/T5252a.hs 
b/tests/ghc-regress/deSugar/should_compile/T5252a.hs
new file mode 100644
index 0000000..ff1704a
--- /dev/null
+++ b/tests/ghc-regress/deSugar/should_compile/T5252a.hs
@@ -0,0 +1,5 @@
+module T5252a( S(..), T ) where
+
+data T = MkT Int Int
+
+data S = MkS {-# UNPACK #-}!T Int
diff --git a/tests/ghc-regress/deSugar/should_compile/all.T 
b/tests/ghc-regress/deSugar/should_compile/all.T
index 6b85275..0db20f9 100644
--- a/tests/ghc-regress/deSugar/should_compile/all.T
+++ b/tests/ghc-regress/deSugar/should_compile/all.T
@@ -84,3 +84,7 @@ test('T4870',
      multimod_compile,
      ['T4870', '-v0'])
 test('T5117', normal, compile, [''])
+test('T5252',
+     extra_clean(['T5252a.hi', 'T5252a.o']),
+     run_command, 
+     ['$MAKE -s --no-print-directory T5252'])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to