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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/9fa6f86a6dd5cab01be6b51a3d9afa9ff2c4554a

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

commit 9fa6f86a6dd5cab01be6b51a3d9afa9ff2c4554a
Author: Simon Peyton Jones <[email protected]>
Date:   Wed Aug 22 17:25:17 2012 +0100

    Test Trac #7176

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

 tests/polykinds/T7176.hs |   15 +++++++++++++++
 tests/polykinds/all.T    |    1 +
 2 files changed, 16 insertions(+), 0 deletions(-)

diff --git a/tests/polykinds/T7176.hs b/tests/polykinds/T7176.hs
new file mode 100644
index 0000000..e3416d1
--- /dev/null
+++ b/tests/polykinds/T7176.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE TypeFamilies, DataKinds, PolyKinds, GADTs, RankNTypes #-}
+
+module T7176 where
+
+type family Sing (a :: b)
+
+data SMaybe (a :: Maybe c) where
+   SNothing :: SMaybe Nothing
+   SJust :: Sing a -> SMaybe (Just a)
+type instance Sing (a :: Maybe d) = SMaybe a
+
+sIsJust :: forall (a :: Maybe e). Sing a -> ()
+sIsJust SNothing = ()
+sIsJust (SJust _) = ()
+
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index fc7b08a..e3b14f6 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -62,4 +62,5 @@ test('T7073', normal, compile,[''])
 test('T7128', normal, compile,[''])
 test('T7151', normal, compile_fail,[''])
 test('T7095', normal, compile,[''])
+test('T7176', normal, compile,[''])
 



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

Reply via email to