[commit: testsuite] master: Test Trac #8474 (04f6ddd)
git at git.haskell.org
git at git.haskell.org
Fri Oct 25 13:46:20 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/04f6ddd0e56fd21a399d17634533dfaf89b25773/testsuite
>---------------------------------------------------------------
commit 04f6ddd0e56fd21a399d17634533dfaf89b25773
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Oct 25 14:46:04 2013 +0100
Test Trac #8474
>---------------------------------------------------------------
04f6ddd0e56fd21a399d17634533dfaf89b25773
tests/typecheck/should_compile/T8474.hs | 19 +++++++++++++++++++
tests/typecheck/should_compile/all.T | 1 +
2 files changed, 20 insertions(+)
diff --git a/tests/typecheck/should_compile/T8474.hs b/tests/typecheck/should_compile/T8474.hs
new file mode 100644
index 0000000..72df3b8
--- /dev/null
+++ b/tests/typecheck/should_compile/T8474.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE ImplicitParams #-}
+module T8474 where
+
+data D = D Int deriving Show
+
+-- In 7.7 this took exponential time!
+slow_to_compile :: IO ()
+slow_to_compile = do
+ tst1 <- return 1
+
+ let ?tst1 = tst1
+ let ?tst2 = tst1
+ let ?tst3 = tst1
+ let ?tst4 = tst1
+ let ?tst5 = tst1
+ let ?tst6 = tst1
+ let ?tst7 = tst1
+
+ print $ D ?tst1
\ No newline at end of file
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index 0ccd90a..8656cf0 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -411,3 +411,4 @@ test('T7903', normal, compile, [''])
test('TcTypeNatSimple', normal, compile, [''])
test('TcCoercibleCompile', when(compiler_lt('ghc', '7.7'), skip), compile, [''])
test('T8392', normal, compile, [''])
+test('T8474', normal, compile, [''])
More information about the ghc-commits
mailing list