[commit: ghc] master: Test #8851. (1ac9114)

git at git.haskell.org git at git.haskell.org
Fri Mar 7 06:00:37 UTC 2014


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

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

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

commit 1ac91146dc3431742eafd33ed4afc552ca17fb64
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Thu Mar 6 23:44:57 2014 -0500

    Test #8851.


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

1ac91146dc3431742eafd33ed4afc552ca17fb64
 testsuite/tests/deriving/should_compile/T8851.hs |   24 ++++++++++++++++++++++
 testsuite/tests/deriving/should_compile/all.T    |    1 +
 2 files changed, 25 insertions(+)

diff --git a/testsuite/tests/deriving/should_compile/T8851.hs b/testsuite/tests/deriving/should_compile/T8851.hs
new file mode 100644
index 0000000..84f0ad4
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8851.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
+module T8851 where
+
+import Control.Applicative
+
+class Parsing m where
+  notFollowedBy :: (Monad m, Show a) => m a -> m ()
+
+data Parser a
+instance Parsing Parser where
+  notFollowedBy = undefined
+
+instance Functor Parser where
+  fmap = undefined
+instance Applicative Parser where
+  pure = undefined
+  (<*>) = undefined
+instance Monad Parser where
+  return = undefined
+  (>>=) = undefined
+
+newtype MyParser a = MkMP (Parser a)
+  deriving Parsing
\ No newline at end of file
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index a7cc3df..8620c36 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -44,3 +44,4 @@ test('AutoDeriveTypeable', normal, compile, [''])
 test('T8138', reqlib('primitive'), compile, ['-O2'])
 test('T8631', normal, compile, [''])
 test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0'])
+test('T8851', expect_broken(8851), compile, [''])
\ No newline at end of file



More information about the ghc-commits mailing list