[commit: testsuite] master: Test cases for context stack overflow (5a880de)
git at git.haskell.org
git at git.haskell.org
Wed Nov 20 10:24:09 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/5a880de8b2c2eb1fbae771f6f5367055570483fd/testsuite
>---------------------------------------------------------------
commit 5a880de8b2c2eb1fbae771f6f5367055570483fd
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Wed Nov 20 09:38:53 2013 +0000
Test cases for context stack overflow
one for constraints, one for type families
>---------------------------------------------------------------
5a880de8b2c2eb1fbae771f6f5367055570483fd
tests/typecheck/should_fail/ContextStack1.hs | 11 +++++++++++
tests/typecheck/should_fail/ContextStack1.stderr | 7 +++++++
.../T5837.hs => typecheck/should_fail/ContextStack2.hs} | 2 +-
tests/typecheck/should_fail/ContextStack2.stderr | 9 +++++++++
tests/typecheck/should_fail/all.T | 2 ++
5 files changed, 30 insertions(+), 1 deletion(-)
diff --git a/tests/typecheck/should_fail/ContextStack1.hs b/tests/typecheck/should_fail/ContextStack1.hs
new file mode 100644
index 0000000..1515bba
--- /dev/null
+++ b/tests/typecheck/should_fail/ContextStack1.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE UndecidableInstances, FlexibleInstances #-}
+
+module ContextStack1 where
+
+class Cls a where meth :: a
+
+instance Cls [a] => Cls a
+
+t :: ()
+t = meth
+
diff --git a/tests/typecheck/should_fail/ContextStack1.stderr b/tests/typecheck/should_fail/ContextStack1.stderr
new file mode 100644
index 0000000..425c79a
--- /dev/null
+++ b/tests/typecheck/should_fail/ContextStack1.stderr
@@ -0,0 +1,7 @@
+
+ContextStack1.hs:10:5:
+ Context reduction stack overflow; size = 11
+ Use -fcontext-stack=N to increase stack size to N
+ Cls [[[[[[[[[[[()]]]]]]]]]]]
+ In the expression: meth
+ In an equation for ‛t’: t = meth
diff --git a/tests/perf/compiler/T5837.hs b/tests/typecheck/should_fail/ContextStack2.hs
similarity index 85%
copy from tests/perf/compiler/T5837.hs
copy to tests/typecheck/should_fail/ContextStack2.hs
index c2d0f10..5c50b02 100644
--- a/tests/perf/compiler/T5837.hs
+++ b/tests/typecheck/should_fail/ContextStack2.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE AllowAmbiguousTypes, TypeFamilies #-}
-module T5837 where
+module ContextStack2 where
type family TF a :: *
type instance TF (a,b) = (TF a, TF b)
diff --git a/tests/typecheck/should_fail/ContextStack2.stderr b/tests/typecheck/should_fail/ContextStack2.stderr
new file mode 100644
index 0000000..1a48a62
--- /dev/null
+++ b/tests/typecheck/should_fail/ContextStack2.stderr
@@ -0,0 +1,9 @@
+
+ContextStack2.hs:8:6:
+ Context reduction stack overflow; size = 11
+ Use -fcontext-stack=N to increase stack size to N
+ (TF (TF (TF (TF (TF (TF (TF (TF (TF (TF (TF a)))))))))),
+ TF (TF (TF (TF (TF (TF (TF (TF (TF (TF (TF Int)))))))))))
+ ~ TF (TF (TF (TF (TF (TF (TF (TF (TF (TF a)))))))))
+ In the ambiguity check for: forall a. a ~ TF (a, Int) => Int
+ In the type signature for ‛t’: t :: a ~ TF (a, Int) => Int
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 749ea32..b6530b1 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -325,3 +325,5 @@ test('T8392a', normal, compile_fail, [''])
test('T8428', normal, compile_fail, [''])
test('T8450', normal, compile_fail, [''])
test('T8514', normal, compile_fail, [''])
+test('ContextStack1', normal, compile_fail, ['-fcontext-stack=10'])
+test('ContextStack2', normal, compile_fail, ['-fcontext-stack=10'])
More information about the ghc-commits
mailing list