[commit: ghc] master: Test Trac #11552 (c9ac9de)

git at git.haskell.org git at git.haskell.org
Mon Feb 8 17:47:23 UTC 2016


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

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

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

commit c9ac9de78254fb6bf463fd6370be7a7214b3e649
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Feb 8 17:38:26 2016 +0000

    Test Trac #11552


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

c9ac9de78254fb6bf463fd6370be7a7214b3e649
 testsuite/tests/typecheck/should_compile/T11552.hs | 21 +++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 22 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T11552.hs b/testsuite/tests/typecheck/should_compile/T11552.hs
new file mode 100644
index 0000000..1c5a54b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11552.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE InstanceSigs        #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module T11552 where
+
+newtype MaybeT m a =
+  MaybeT { runMaybeT :: m (Maybe a) }
+
+instance (Functor m) => Functor (MaybeT m) where
+  fmap f (MaybeT ma) =
+    MaybeT $ (fmap . fmap) f ma
+
+instance forall f . (Applicative f) => Applicative (MaybeT f) where
+  pure :: a -> MaybeT f a
+  pure x = MaybeT (pure (pure x))
+
+  (<*>) :: forall a b . Applicative f => MaybeT f (a -> b) -> MaybeT f a -> MaybeT f b
+  (MaybeT fab) <*> (MaybeT mma) =
+   let fab' :: f (Maybe (a -> b))
+       fab' = fab
+   in MaybeT $ undefined
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index e4b1e41..c547d6c 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -504,3 +504,4 @@ test('T11397', normal, compile, [''])
 test('T11458', normal, compile, [''])
 test('T11516', expect_broken(11516), compile, [''])
 test('T11524', normal, compile, [''])
+test('T11552', normal, compile, [''])



More information about the ghc-commits mailing list