[commit: packages/directory] master: Refactor dispatch-tests.hs:quoteCmdArgs (4b0ccb4)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:50:47 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/4b0ccb4d2508dbbc0925d779f184a68172f009ee/directory
>---------------------------------------------------------------
commit 4b0ccb4d2508dbbc0925d779f184a68172f009ee
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Mon May 25 02:48:19 2015 -0400
Refactor dispatch-tests.hs:quoteCmdArgs
>---------------------------------------------------------------
4b0ccb4d2508dbbc0925d779f184a68172f009ee
tools/dispatch-tests.hs | 21 +++++++++++----------
1 file changed, 11 insertions(+), 10 deletions(-)
diff --git a/tools/dispatch-tests.hs b/tools/dispatch-tests.hs
index 2b9d6df..963060f 100644
--- a/tools/dispatch-tests.hs
+++ b/tools/dispatch-tests.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
module Main (main) where
import Prelude (($), (.), (=<<), (==), Eq, IO, Int, String,
- id, fromIntegral, otherwise, unwords)
+ fromIntegral, otherwise, unwords)
import Data.Functor ((<$>))
import Data.Monoid ((<>), mconcat)
import Foreign (Ptr)
@@ -46,18 +46,19 @@ rawSystem cmd args =
-- handle the different quoting rules in CMD.EXE vs POSIX shells
quoteCmdArgs :: [String] -> String
-quoteCmdArgs cmdArgs =
+quoteCmdArgs cmdArgs = quoted'
+ where
+ quoted = unwords (quote <$> cmdArgs)
#ifdef mingw32_HOST_OS
- -- 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
- let quote s = "\"" <> replaceElem '"' "\"\"" s <> "\""
- in (\ s -> "\"" <> s <> "\"") $
+ -- 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
+ quote s = "\"" <> replaceElem '"' "\"\"" s <> "\""
+ quoted' = "\"" <> quoted <> "\""
#else
- let quote s = "'" <> replaceElem '\'' "'\\''" s <> "'"
- in id $
+ quote s = "'" <> replaceElem '\'' "'\\''" s <> "'"
+ quoted' = quoted
#endif
- unwords (quote <$> cmdArgs)
replaceElem :: Eq a => a -> [a] -> [a] -> [a]
replaceElem match repl = mconcat . (replace <$>)
More information about the ghc-commits
mailing list