[commit: ghc] master: Add testcase for #15050 (f04ac4d)

git at git.haskell.org git at git.haskell.org
Mon Apr 23 17:03:51 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f04ac4d4d0811f48c68fecacefb262039ee33239/ghc

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

commit f04ac4d4d0811f48c68fecacefb262039ee33239
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Mon Apr 23 13:02:50 2018 -0400

    Add testcase for #15050
    
    so that we notice if someone accidentially implements this...


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

f04ac4d4d0811f48c68fecacefb262039ee33239
 testsuite/tests/typecheck/should_compile/T15050.hs | 21 +++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 22 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T15050.hs b/testsuite/tests/typecheck/should_compile/T15050.hs
new file mode 100644
index 0000000..ed5f095
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T15050.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE GADTs #-}
+module T15050 where
+data P a = P
+data T1 a where
+  MkT1a :: forall a.              P a               -> T1 a
+  MkT1b :: forall a.              P a               -> T1 a
+  MkT1c :: forall a.              P a               -> T1 a
+  MkT2  :: forall a.              P a               -> T1 (a,a)
+  MkT3  :: forall a b. b ~ Int => P a -> P b        -> T1 a
+  MkT4  :: forall a b.            P a -> P b        -> T1 a
+  MkT5  :: forall a b c. b ~ c => P a -> P b -> P c -> T1 a
+
+foo :: T1 (Int, Int) -> ()
+foo (MkT1a (P::P (Int,Int)))    = ()
+foo (MkT1b (P::P (Int,x)))      = (() :: x ~ Int => ())
+foo (MkT1c (P::P x))            = (() :: x ~ (Int,Int) => ())
+foo (MkT2  (P::P x))            = (() :: x ~ Int => ())
+foo (MkT3  P (P::P Int))        = ()
+foo (MkT4  P (P::P b))          = ()
+foo (MkT5  P (P::P b) (P::P b)) = ()
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 70e52cf..80a8b0e 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -602,3 +602,4 @@ test('T14934', [extra_files(['T14934.hs', 'T14934a.hs'])], run_command,
 test('T13643', normal, compile, [''])
 test('SplitWD', normal, compile, [''])
 test('T14441', normal, compile, [''])
+test('T15050', [expect_broken(15050)], compile, [''])



More information about the ghc-commits mailing list