[commit: ghc] master: Testsuite: add test for #10997 (68a084f)
git at git.haskell.org
git at git.haskell.org
Wed Oct 21 12:31:58 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/68a084f378fbab857ccea81643eee15254b2917b/ghc
>---------------------------------------------------------------
commit 68a084f378fbab857ccea81643eee15254b2917b
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date: Wed Oct 21 14:31:39 2015 +0200
Testsuite: add test for #10997
>---------------------------------------------------------------
68a084f378fbab857ccea81643eee15254b2917b
testsuite/tests/typecheck/should_compile/T10997.hs | 15 +++++++++++++++
testsuite/tests/typecheck/should_compile/T10997a.hs | 17 +++++++++++++++++
testsuite/tests/typecheck/should_compile/all.T | 2 ++
3 files changed, 34 insertions(+)
diff --git a/testsuite/tests/typecheck/should_compile/T10997.hs b/testsuite/tests/typecheck/should_compile/T10997.hs
new file mode 100644
index 0000000..18ec4ac
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10997.hs
@@ -0,0 +1,15 @@
+module T10997 where
+
+import T10997a
+
+{- With ghc-7.10.2:
+
+ The interface for ‘T10997a’
+ Declaration for Just'
+ Pattern synonym Just':
+ Iface type variable out of scope: k
+ Cannot continue after interface file error
+-}
+
+bar :: (Showable a) => Maybe a -> Maybe a
+bar (Just' a) = Just' a
diff --git a/testsuite/tests/typecheck/should_compile/T10997a.hs b/testsuite/tests/typecheck/should_compile/T10997a.hs
new file mode 100644
index 0000000..dc85d62
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10997a.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE PatternSynonyms, ViewPatterns, ConstraintKinds, TypeFamilies, PolyKinds, KindSignatures #-}
+module T10997a where
+
+import GHC.Exts
+
+type family Showable (a :: k) :: Constraint where
+ Showable (a :: *) = (Show a)
+ Showable a = ()
+
+extractJust :: Maybe a -> (Bool, a)
+extractJust (Just a) = (True, a)
+extractJust _ = (False, undefined)
+
+pattern Just' :: () => (Showable a) => a -> (Maybe a)
+pattern Just' a <- (extractJust -> (True, a)) where
+ Just' a = Just a
+
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index ed0c8e1..d7271b7 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -479,3 +479,5 @@ test('T10770a', expect_broken(10770), compile, [''])
test('T10770b', expect_broken(10770), compile, [''])
test('T10935', normal, compile, [''])
test('T10971a', normal, compile, [''])
+test('T10997', expect_broken(10997),
+ multi_compile, ['T10997', [('T10997a.hs', '')], '-v0'])
More information about the ghc-commits
mailing list