Skip to content
Snippets Groups Projects
Commit adbc8c18 authored by Richard Eisenberg's avatar Richard Eisenberg Committed by Austin Seipp
Browse files

Test #8851.

(cherry picked from commit 1ac91146)

Conflicts:
	testsuite/tests/deriving/should_compile/all.T
parent c8418d18
No related branches found
No related tags found
No related merge requests found
{-# 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
......@@ -45,3 +45,4 @@ test('T8138', reqlib('primitive'), compile, ['-O2'])
test('T8631', normal, compile, [''])
test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0'])
test('T8865', normal, compile, [''])
test('T8851', expect_broken(8851), compile, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment