[commit: ghc] master: Test Trac #10562 (c7b6fb5)

git at git.haskell.org git at git.haskell.org
Thu Jun 25 14:51:25 UTC 2015


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

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

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

commit c7b6fb59eca478650dcb391a6f424e3c42a155dc
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Jun 25 15:49:09 2015 +0100

    Test Trac #10562


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

c7b6fb59eca478650dcb391a6f424e3c42a155dc
 testsuite/tests/typecheck/should_compile/T10562.hs | 14 ++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 15 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T10562.hs b/testsuite/tests/typecheck/should_compile/T10562.hs
new file mode 100644
index 0000000..30b1b0c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10562.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE GADTs, TypeFamilies #-}
+module T10562 where
+
+type family Flip a
+
+data QueryRep qtyp a where
+    QAtom :: a -> QueryRep () a
+    QOp   :: QueryRep (Flip qtyp) a -> QueryRep qtyp a
+
+instance Eq (QueryRep qtyp a) where
+  (==) = error "urk"
+
+instance (Ord a) => Ord (QueryRep qtyp a) where
+  compare (QOp a) (QOp b) = a `compare` b
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 8165087..89227c6 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -463,3 +463,4 @@ test('T10494', normal, compile, [''])
 test('T10493', normal, compile, [''])
 test('T10428', normal, compile, [''])
 test('RepArrow', normal, compile, [''])
+test('T10562', normal, compile, [''])



More information about the ghc-commits mailing list