[commit: testsuite] master: Add a test for #7848 (1ec6d9f)
Ian Lynagh
igloo at earth.li
Sun Apr 21 18:00:35 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/1ec6d9f3fcb5f31c964e8269c16e1841c9663012
>---------------------------------------------------------------
commit 1ec6d9f3fcb5f31c964e8269c16e1841c9663012
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun Apr 21 14:42:24 2013 +0100
Add a test for #7848
>---------------------------------------------------------------
tests/parser/should_fail/T7848.hs | 11 +++++++++++
tests/parser/should_fail/T7848.stderr | 19 +++++++++++++++++++
tests/parser/should_fail/all.T | 1 +
3 files changed, 31 insertions(+), 0 deletions(-)
diff --git a/tests/parser/should_fail/T7848.hs b/tests/parser/should_fail/T7848.hs
new file mode 100644
index 0000000..25f0af7
--- /dev/null
+++ b/tests/parser/should_fail/T7848.hs
@@ -0,0 +1,11 @@
+
+module T7848 where
+
+data A = (:&&) Int Int | A Int Int
+
+x (+) ((&)@z) ((:&&) a b) (c :&& d) (e `A` f) (A g h) = y
+ where infixl 3 `y`
+ y _ = (&)
+ {-# INLINE (&) #-}
+ {-# SPECIALIZE (&) :: a #-}
+ (&) = x
diff --git a/tests/parser/should_fail/T7848.stderr b/tests/parser/should_fail/T7848.stderr
new file mode 100644
index 0000000..f37d356
--- /dev/null
+++ b/tests/parser/should_fail/T7848.stderr
@@ -0,0 +1,19 @@
+
+T7848.hs:10:9:
+ Couldn't match expected type âforall a. aâ
+ with actual type ât -> t1 -> A -> A -> A -> A -> t2â
+ Relevant bindings include
+ x :: t -> t1 -> A -> A -> A -> A -> t2 (bound at T7848.hs:6:1)
+ (+) :: t (bound at T7848.hs:6:3)
+ (&) :: t1 (bound at T7848.hs:6:8)
+ z :: t1 (bound at T7848.hs:6:12)
+ In the SPECIALISE pragma {-# SPECIALIZE (&) :: a #-}
+ In an equation for âxâ:
+ x (+) ((&)@z) ((:&&) a b) (c :&& d) (e `A` f) (A g h)
+ = y
+ where
+ infixl 3 `y`
+ y _ = (&)
+ {-# INLINE (&) #-}
+ {-# SPECIALIZE (&) :: a #-}
+ (&) = x
diff --git a/tests/parser/should_fail/all.T b/tests/parser/should_fail/all.T
index a09b76d..ebd768c 100644
--- a/tests/parser/should_fail/all.T
+++ b/tests/parser/should_fail/all.T
@@ -77,3 +77,4 @@ test('ParserNoMultiWayIf', when(compiler_lt('ghc', '7.5'), skip), compile_fail,
test('T5425', normal, compile_fail, [''])
test('T984', normal, compile_fail, [''])
+test('T7848', normal, compile_fail, ['-dppr-user-length=100'])
More information about the ghc-commits
mailing list