[commit: packages/directory] master: Fix warnings in dispatch-tests.hs on GHC 7.10 (e3c63d8)

git at git.haskell.org git at git.haskell.org
Fri Dec 18 09:50:10 UTC 2015


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

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

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

commit e3c63d88db11fe00c8057a04dbaaba22897cc80b
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Fri Apr 10 19:52:46 2015 -0400

    Fix warnings in dispatch-tests.hs on GHC 7.10


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

e3c63d88db11fe00c8057a04dbaaba22897cc80b
 tools/dispatch-tests.hs | 20 ++++++++++++--------
 1 file changed, 12 insertions(+), 8 deletions(-)

diff --git a/tools/dispatch-tests.hs b/tools/dispatch-tests.hs
index 598cd8b..2b9d6df 100644
--- a/tools/dispatch-tests.hs
+++ b/tools/dispatch-tests.hs
@@ -1,9 +1,12 @@
 {-# LANGUAGE CPP, ForeignFunctionInterface #-}
 module Main (main) where
+import Prelude (($), (.), (=<<), (==), Eq, IO, Int, String,
+                id, fromIntegral, otherwise, unwords)
+import Data.Functor ((<$>))
+import Data.Monoid ((<>), mconcat)
 import Foreign (Ptr)
 import Foreign.C (CChar(..), CInt(..), withCString)
-import Data.Functor ((<$>))
-import System.Directory ()     -- to make sure `directory` is built beforehand
+import System.Directory ()        -- to ensure `directory` is built beforehand
 import System.Environment (getArgs)
 import System.Exit (ExitCode(ExitSuccess, ExitFailure), exitWith)
 
@@ -19,7 +22,7 @@ main = do
                  ExitFailure _ -> []
 
   args <- getArgs
-  let command : arguments = prefix ++ ["sh", "tools/run-tests"] ++ args
+  let command : arguments = prefix <> ["sh", "tools/run-tests"] <> args
   exitWith =<< normalizeExitCode <$> rawSystem command arguments
 
 makeExitCode :: Int -> ExitCode
@@ -48,15 +51,16 @@ quoteCmdArgs cmdArgs =
   -- the arcane quoting rules require us to add an extra set of quotes
   -- around the entire thing: see `help cmd` or look at
   -- https://superuser.com/a/238813
-  "\"" ++ unwords (quote <$> cmdArgs) ++ "\""
-  where quote s = "\"" ++ replaceElem '"' "\"\"" s ++ "\""
+  let quote s = "\"" <> replaceElem '"' "\"\"" s <> "\""
+  in (\ s -> "\"" <> s <> "\"") $
 #else
-  unwords (quote <$> cmdArgs)
-  where quote s = "'" ++ replaceElem '\'' "'\\''" s ++ "'"
+  let quote s = "'" <> replaceElem '\'' "'\\''" s <> "'"
+  in id $
 #endif
+     unwords (quote <$> cmdArgs)
 
 replaceElem :: Eq a => a -> [a] -> [a] -> [a]
-replaceElem match repl = concat . (replace <$>)
+replaceElem match repl = mconcat . (replace <$>)
   where replace c | c == match = repl
                   | otherwise  = [c]
 



More information about the ghc-commits mailing list