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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/a7035aade7769261f8faa157f00e171dc2e9ffaa

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

commit a7035aade7769261f8faa157f00e171dc2e9ffaa
Author: Simon Peyton Jones <[email protected]>
Date:   Mon Apr 30 16:14:30 2012 +0100

    Test Trac #6055

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

 tests/typecheck/should_compile/T6055.hs |   45 +++++++++++++++++++++++++++++++
 tests/typecheck/should_compile/all.T    |    1 +
 2 files changed, 46 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/T6055.hs 
b/tests/typecheck/should_compile/T6055.hs
new file mode 100644
index 0000000..beede55
--- /dev/null
+++ b/tests/typecheck/should_compile/T6055.hs
@@ -0,0 +1,45 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE FunctionalDependencies #-}
+{-# LANGUAGE EmptyDataDecls #-}
+module T6055 where
+
+data Int1  = Int1
+data Word1 = Word1
+
+data D1
+data D2
+
+
+class Succ x y | x -> y
+instance Succ D1 D2
+
+
+class Add' x y z | x y -> z
+
+instance Succ y z => Add' D1 y z
+
+
+class (Add' x y z) => Add x y z
+instance (Add' D1 y z) => Add D1 y z
+
+
+class IsSized a s | a -> s where
+
+instance IsSized Int1  D1
+instance IsSized Word1 D1
+
+instance (IsSized a s, Add s s ns) =>
+   IsSized (Pair a) ns where
+
+data Pair a = Pair a a
+
+
+switchFPPred ::
+   (IsSized v0 s, IsSized v1 s) =>
+   v0 -> v1
+switchFPPred = undefined
+
+cmpss :: Pair Word1 -> Pair Int1
+cmpss = switchFPPred
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index bccb1fa..58664a4 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -378,3 +378,4 @@ test('T5792',normal,run_command,
 
 test('PolytypeDecomp', normal, compile, [''])
 test('T6011', normal, compile, [''])
+test('T6055', normal, compile, [''])



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

Reply via email to