diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs
index 095d6b8ddf786d21748019527cb6327ea0442f22..2d092921ddebf8a153ffbb1bb0d73dd07bfc8c84 100644
--- a/Cabal/Distribution/Simple/Haddock.hs
+++ b/Cabal/Distribution/Simple/Haddock.hs
@@ -84,14 +84,16 @@ import Language.Haskell.Extension
import Control.Monad ( when, forM_ )
+import Data.Char ( isSpace )
import Data.Either ( rights )
import Data.Monoid
+import Data.Foldable ( foldl' )
import Data.Maybe ( fromMaybe, listToMaybe )
import System.Directory (doesFileExist)
import System.FilePath ( (</>), (<.>)
, normalise, splitPath, joinPath, isAbsolute )
-import System.IO (hClose, hPutStrLn, hSetEncoding, utf8)
+import System.IO (hClose, hPutStr, hPutStrLn, hSetEncoding, utf8)
import Distribution.Version
-- ------------------------------------------------------------------------------
@@ -467,7 +469,7 @@ renderArgs :: Verbosity
-> IO a
renderArgs verbosity tmpFileOpts version comp args k = do
let haddockSupportsUTF8 = version >= Version [2,14,4] []
- haddockSupportsResponseFiles = version > Version [2,16,1] []
+ haddockSupportsResponseFiles = version > Version [2,16,2] []
createDirectoryIfMissingVerbose verbosity True outputDir
withTempFileEx tmpFileOpts outputDir "haddock-prologue.txt" $
\prologueFileName h -> do
@@ -482,7 +484,7 @@ renderArgs verbosity tmpFileOpts version comp args k = do
withTempFileEx tmpFileOpts outputDir "haddock-response.txt" $
\responseFileName hf -> do
when haddockSupportsUTF8 (hSetEncoding hf utf8)
- mapM_ (hPutStrLn hf) renderedArgs
+ hPutStr hf $ unlines $ map escapeArg renderedArgs
hClose hf
let respFile = "@" ++ responseFileName
k ([respFile], result)
@@ -500,6 +502,19 @@ renderArgs verbosity tmpFileOpts version comp args k = do
pkgstr = display $ packageName pkgid
pkgid = arg argPackageName
arg f = fromFlag $ f args
+ -- Support a gcc-like response file syntax. Each separate
+ -- argument and its possible parameter(s), will be separated in the
+ -- response file by an actual newline; all other whitespace,
+ -- single quotes, double quotes, and the character used for escaping
+ -- (backslash) are escaped. The called program will need to do a similar
+ -- inverse operation to de-escape and re-constitute the argument list.
+ escape cs c
+ | isSpace c
+ || '\\' == c
+ || '\'' == c
+ || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result
+ | otherwise = c:cs
+ escapeArg = reverse . foldl' escape []
renderPureArgs :: Version -> Compiler -> HaddockArgs -> [String]
renderPureArgs version comp args = concat