[commit: testsuite] master: Test Trac #7891 and #7903 (f923892)

Simon Peyton Jones simonpj at microsoft.com
Wed May 15 16:56:37 CEST 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

https://github.com/ghc/testsuite/commit/f9238920d4c1f587b4f7db59638921d82a03c747

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

commit f9238920d4c1f587b4f7db59638921d82a03c747
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed May 15 15:55:44 2013 +0100

    Test Trac #7891 and #7903

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

 tests/typecheck/should_compile/T7891.hs |   37 +++++++++++++++++++++++++++++++
 tests/typecheck/should_compile/T7903.hs |    4 +++
 tests/typecheck/should_compile/all.T    |    2 +
 3 files changed, 43 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/T7891.hs b/tests/typecheck/should_compile/T7891.hs
new file mode 100644
index 0000000..82334d4
--- /dev/null
+++ b/tests/typecheck/should_compile/T7891.hs
@@ -0,0 +1,37 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module T7891 where
+
+newtype T = T (forall t. t -> t)
+
+tf :: T
+tf = T id
+
+-- Can't write this type signature:
+-- f :: t -> t
+T f = tf
+
+-- But with an indirection we can:
+g :: t -> t
+g = f
+
+-- We can still use f as it were fully polymorphic (which is good):
+a :: ()
+a = f ()
+b :: Char
+b = f 'b'
+
+-------------
+
+class C t where
+  data F t :: *
+  mkF :: t -> F t
+
+instance C () where
+  data F () = FUnit (forall t. t -> t)
+  mkF () = FUnit id
+
+-- Can't write a type for f here either:
+k :: t -> t
+FUnit k = mkF ()
diff --git a/tests/typecheck/should_compile/T7903.hs b/tests/typecheck/should_compile/T7903.hs
new file mode 100644
index 0000000..43f97a0
--- /dev/null
+++ b/tests/typecheck/should_compile/T7903.hs
@@ -0,0 +1,4 @@
+module T7903 where
+
+instance Eq (((->) a) b)
+instance (Ord b) => Ord (((->) a) b)
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index 68c9b81..1fc81cb 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -402,3 +402,5 @@ test('T7827', normal, compile, [''])
 test('T7875', normal, compile, [''])
 test('T7268', normal, compile, [''])
 test('T7888', normal, compile, [''])
+test('T7891', normal, compile, [''])
+test('T7903', normal, compile, [''])





More information about the ghc-commits mailing list