[commit: ghc] master: testsuite: Add ClassOperator testcase (9f23dd9)
git at git.haskell.org
git at git.haskell.org
Mon Dec 21 12:41:48 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/9f23dd9d05eb0945fa7a60492d2f2721d364327b/ghc
>---------------------------------------------------------------
commit 9f23dd9d05eb0945fa7a60492d2f2721d364327b
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Sun Dec 20 15:21:10 2015 +0100
testsuite: Add ClassOperator testcase
This is derived from Haddock's `Operators` `html-test`, which appears to
fail with GHC master yet compiles with 7.10.2
Reviewers: simonpj, austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1667
GHC Trac Issues: #11264
>---------------------------------------------------------------
9f23dd9d05eb0945fa7a60492d2f2721d364327b
.../tests/typecheck/should_compile/ClassOperator.hs | 21 +++++++++++++++++++++
testsuite/tests/typecheck/should_compile/all.T | 1 +
2 files changed, 22 insertions(+)
diff --git a/testsuite/tests/typecheck/should_compile/ClassOperator.hs b/testsuite/tests/typecheck/should_compile/ClassOperator.hs
new file mode 100644
index 0000000..6d41d11
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/ClassOperator.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE PatternSynonyms, TypeOperators, TypeFamilies, MultiParamTypeClasses, GADTs #-}
+
+module ClassOperator where
+
+-- | Class with fixity, including associated types
+class a ><> b where
+ type a <>< b :: *
+ data a ><< b
+ (>><), (<<>) :: a -> b -> ()
+
+ -- | Multiple fixities
+ (**>), (**<), (>**), (<**) :: a -> a -> ()
+
+infixr 1 ><>
+infixl 2 <><
+infixl 3 ><<
+infixr 4 >><
+infixl 5 <<>
+
+infixr 8 **>, >**
+infixl 8 **<, <**
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index ae2aa94..5b09782 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -481,3 +481,4 @@ test('T10935', normal, compile, [''])
test('T10971a', normal, compile, [''])
test('T11237', normal, compile, [''])
test('T10592', normal, compile, [''])
+test('ClassOperator', expect_broken(11264), compile, [''])
More information about the ghc-commits
mailing list