[commit: ghc] master: Add a test for d3af980 (#5682) (5a57675)
git at git.haskell.org
git at git.haskell.org
Thu Feb 20 12:13:07 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/5a576754d745171422d13cd1dba69dd874714cf1/ghc
>---------------------------------------------------------------
commit 5a576754d745171422d13cd1dba69dd874714cf1
Author: Austin Seipp <austin at well-typed.com>
Date: Thu Feb 20 06:12:06 2014 -0600
Add a test for d3af980 (#5682)
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
5a576754d745171422d13cd1dba69dd874714cf1
testsuite/tests/parser/should_compile/T5682.hs | 3 ++-
1 file changed, 2 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/parser/should_compile/T5682.hs b/testsuite/tests/parser/should_compile/T5682.hs
index bfd6752..cdfe46f 100644
--- a/testsuite/tests/parser/should_compile/T5682.hs
+++ b/testsuite/tests/parser/should_compile/T5682.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DataKinds, DeriveDataTypeable, StandaloneDeriving, TypeOperators #-}
+{-# LANGUAGE DataKinds, PolyKinds, DeriveDataTypeable, StandaloneDeriving, TypeOperators #-}
module T5682 where
@@ -10,3 +10,4 @@ data Foo = Bool :+: Bool
type X = True ':+: False
deriving instance Typeable '(:+:)
+deriving instance Typeable '(,,)
More information about the ghc-commits
mailing list