[commit: testsuite] master: SpecConstr infinite specialisation: test for #5550 (7fb4ac4)

Amos Robinson amos.robinson at gmail.com
Wed Apr 3 08:32:59 CEST 2013


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

On branch  : master

https://github.com/ghc/testsuite/commit/7fb4ac41a673b68fb9ff4383f116d6318aa217fe

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

commit 7fb4ac41a673b68fb9ff4383f116d6318aa217fe
Author: Amos Robinson <amos.robinson at gmail.com>
Date:   Wed Apr 3 17:28:41 2013 +1100

    SpecConstr infinite specialisation: test for #5550

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

 tests/simplCore/should_compile/T5550.hs     |   11 +++++++++++
 tests/simplCore/should_compile/T5550.stderr |    3 +++
 tests/simplCore/should_compile/all.T        |    1 +
 3 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/simplCore/should_compile/T5550.hs b/tests/simplCore/should_compile/T5550.hs
new file mode 100644
index 0000000..025da50
--- /dev/null
+++ b/tests/simplCore/should_compile/T5550.hs
@@ -0,0 +1,11 @@
+module T5550 where
+
+import GHC.Exts ( SpecConstrAnnotation(..) )
+
+data SPEC = SPEC | SPEC2
+{-# ANN type SPEC ForceSpecConstr #-}
+
+loop :: SPEC -> [Int] -> [Int] -> [Int]
+loop SPEC z [] = z
+loop SPEC z (x:xs) = loop SPEC (x:z) xs
+
diff --git a/tests/simplCore/should_compile/T5550.stderr b/tests/simplCore/should_compile/T5550.stderr
new file mode 100644
index 0000000..9ebd8cc
--- /dev/null
+++ b/tests/simplCore/should_compile/T5550.stderr
@@ -0,0 +1,3 @@
+Loading package ghc-prim ... linking ... done.
+Loading package integer-gmp ... linking ... done.
+Loading package base ... linking ... done.
diff --git a/tests/simplCore/should_compile/all.T b/tests/simplCore/should_compile/all.T
index f23061a..8c33ab1 100644
--- a/tests/simplCore/should_compile/all.T
+++ b/tests/simplCore/should_compile/all.T
@@ -164,3 +164,4 @@ test('T7796',
      extra_clean(['T7796.prep']),
      run_command,
      ['$MAKE -s --no-print-directory T7796'])
+test('T5550', normal, compile, [''])





More information about the ghc-commits mailing list