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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2d037a74859b0926e4d43e31c4cf6062750fafe3

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

commit 2d037a74859b0926e4d43e31c4cf6062750fafe3
Author: Simon Peyton Jones <[email protected]>
Date:   Thu Nov 24 12:50:23 2011 +0000

    Test Trac #5655

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

 tests/typecheck/should_compile/T5655.hs |   26 ++++++++++++++++++++++++++
 tests/typecheck/should_compile/all.T    |    2 ++
 2 files changed, 28 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/T5655.hs 
b/tests/typecheck/should_compile/T5655.hs
new file mode 100644
index 0000000..429f50e
--- /dev/null
+++ b/tests/typecheck/should_compile/T5655.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE TypeFamilies, GADTs, ConstraintKinds, Rank2Types #-}
+module T5655 where
+
+import GHC.Prim (Constraint)
+
+class Show a => Twice a where twice :: a -> a
+
+instance Twice Int where twice = (*2)
+
+data ETwice where ETwice :: Twice a => a -> ETwice
+
+class E e where
+    type C e :: * -> Constraint
+    ap :: (forall a. C e a => a -> r) -> e -> r
+
+instance E ETwice where
+    type C ETwice = Twice
+    ap f (ETwice a) = f a
+
+f :: (E e, C e ~ Twice) => e -> ETwice
+f = ap (ETwice . twice)
+
+foo :: ETwice
+foo = ETwice (5 :: Int)
+
+bar = ap print (f foo)
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index a411c6d..d744fd0 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -365,3 +365,5 @@ test('T3743', normal, compile, [''])
 test('T5490', normal, compile, [''])
 test('T5514', normal, compile, [''])
 test('T5581', normal, compile, [''])
+test('T5655', normal, compile, [''])
+



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to