[commit: hsc2hs] master: Fix AMP warnings (2abdfbe)

git at git.haskell.org git at git.haskell.org
Sun Sep 8 15:49:23 CEST 2013


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

On branch  : master
Link       : http://git.haskell.org/?p=hsc2hs.git;a=commit;h=2abdfbeb098ca17416cf0f0d29731d602ffd6029

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

commit 2abdfbeb098ca17416cf0f0d29731d602ffd6029
Author: David Luposchainsky <dluposchainsky at gmail.com>
Date:   Fri Sep 6 19:46:08 2013 +0200

    Fix AMP warnings
    
    Signed-off-by: Austin Seipp <aseipp at pobox.com>


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

2abdfbeb098ca17416cf0f0d29731d602ffd6029
 CrossCodegen.hs |   15 +++++++++++----
 1 file changed, 11 insertions(+), 4 deletions(-)

diff --git a/CrossCodegen.hs b/CrossCodegen.hs
index 7fbd20a..573edcc 100644
--- a/CrossCodegen.hs
+++ b/CrossCodegen.hs
@@ -26,12 +26,13 @@ import System.IO (hPutStr, openFile, IOMode(..), hClose)
 import System.Directory (removeFile)
 import Data.Char (toLower,toUpper,isSpace)
 import Control.Exception (assert, onException)
-import Control.Monad (when,liftM,forM)
+import Control.Monad (when, liftM, forM, ap)
+import Control.Applicative (Applicative(..))
 import Data.Foldable (concatMap)
 import Data.Maybe (fromMaybe)
 import qualified Data.Sequence as S
 import Data.Sequence ((|>),ViewL(..))
-import System.Exit              ( ExitCode(..) )
+import System.Exit ( ExitCode(..) )
 import System.Process
 
 import C
@@ -43,14 +44,20 @@ import HSCParser
 -- and a state counter for unique filename generation.
 -- equivalent to ErrorT String (StateT Int (ReaderT TestMonadEnv IO))
 newtype TestMonad a = TestMonad { runTest :: TestMonadEnv -> Int -> IO (Either String a, Int) }
+
+instance Functor TestMonad where
+    fmap = liftM
+
+instance Applicative TestMonad where
+    pure = return
+    (<*>) = ap
+
 instance Monad TestMonad where
     return a = TestMonad (\_ c -> return $ (Right a, c))
     x >>= fn = TestMonad (\e c -> (runTest x e c) >>=
                                       (\(a,c') -> either (\err -> return (Left err, c'))
                                                          (\result -> runTest (fn result) e c')
                                                          a))
-instance Functor TestMonad where
-    fmap = liftM
 
 data TestMonadEnv = TestMonadEnv {
     testIsVerbose_ :: Bool,





More information about the ghc-commits mailing list