[commit: ghc] master: testsuite: fix T1735_Help/State.hs build failure (AMP) (b30b185)

git at git.haskell.org git at git.haskell.org
Mon Oct 6 21:05:50 UTC 2014


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

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

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

commit b30b185e5c653dfed948d71ce2336be70be3b418
Author: Sergei Trofimovich <slyfox at gentoo.org>
Date:   Mon Oct 6 21:55:02 2014 +0100

    testsuite: fix T1735_Help/State.hs build failure (AMP)
    
    Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>


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

b30b185e5c653dfed948d71ce2336be70be3b418
 testsuite/tests/typecheck/should_run/T1735_Help/State.hs | 10 ++++++++++
 1 file changed, 10 insertions(+)

diff --git a/testsuite/tests/typecheck/should_run/T1735_Help/State.hs b/testsuite/tests/typecheck/should_run/T1735_Help/State.hs
index 7b048eb..d696af7 100644
--- a/testsuite/tests/typecheck/should_run/T1735_Help/State.hs
+++ b/testsuite/tests/typecheck/should_run/T1735_Help/State.hs
@@ -1,6 +1,9 @@
 
 module T1735_Help.State where
 
+import Control.Monad (ap, liftM)
+
+
 newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
 
 instance Monad m => Monad (StateT s m) where
@@ -10,6 +13,13 @@ instance Monad m => Monad (StateT s m) where
         runStateT (k a) s'
     fail str = StateT $ \_ -> fail str
 
+instance Monad m => Functor (StateT s m) where
+    fmap = liftM
+
+instance Monad m => Applicative (StateT s m) where
+    pure  = return
+    (<*>) = ap
+
 get :: Monad m => StateT s m s
 get = StateT $ \s -> return (s, s)
 



More information about the ghc-commits mailing list