[commit: ghc] master: Test Trac #12185 (2e9079f)

git at git.haskell.org git at git.haskell.org
Wed Jun 29 09:38:24 UTC 2016


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

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

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

commit 2e9079ff2be2bbd65e399ef68b46439dbde04961
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jun 29 10:41:55 2016 +0100

    Test Trac #12185


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

2e9079ff2be2bbd65e399ef68b46439dbde04961
 testsuite/tests/typecheck/should_compile/T12185.hs | 20 ++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 21 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T12185.hs b/testsuite/tests/typecheck/should_compile/T12185.hs
new file mode 100644
index 0000000..d2007db
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T12185.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE FlexibleContexts, RankNTypes, TypeFamilies #-}
+
+module T12185 where
+
+class Foo a
+
+newtype Bar r = Pow r deriving (Eq)
+
+instance (Foo r) => Foo (Bar r)
+
+type family Ctx a where Ctx t = (Foo (Bar t), Eq (Bar t))
+
+run :: (forall t . (Ctx t) => t -> Int) -> Int
+run g = undefined
+
+foo :: (Foo (Bar t)) => t -> Int
+foo = undefined
+
+main :: IO ()
+main = print $ run foo
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 9843539..33d91d1 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -529,3 +529,4 @@ test('T11339d', normal, compile, [''])
 test('T11974', normal, compile, [''])
 test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']),
      multimod_compile, ['T12067', '-v0'])
+test('T12185', normal, compile, [''])



More information about the ghc-commits mailing list