[commit: haddock] master, wip/api-annots-ghc-7.10-3: Expand response files in arguments (d567a12)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 08:38:12 UTC 2015
Repository : ssh://git@git.haskell.org/haddock
On branches: master,wip/api-annots-ghc-7.10-3
Link : http://git.haskell.org/haddock.git/commitdiff/d567a12b2d24bab610cd7e8f8014d40c7615e24d
>---------------------------------------------------------------
commit d567a12b2d24bab610cd7e8f8014d40c7615e24d
Author: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
Date: Sat Mar 28 20:38:10 2015 +0000
Expand response files in arguments
Closes #285
>---------------------------------------------------------------
d567a12b2d24bab610cd7e8f8014d40c7615e24d
CHANGES | 1 +
driver/Main.hs | 28 +++++++++++++++++++++++++---
2 files changed, 26 insertions(+), 3 deletions(-)
diff --git a/CHANGES b/CHANGES
index 19639ef..e170bc4 100644
--- a/CHANGES
+++ b/CHANGES
@@ -11,6 +11,7 @@ Changes in version 2.16.1
* Don't print instance safety information in Hoogle (#168)
+ * Expand response files in arguments (#285)
Changes in version 2.16.0
diff --git a/driver/Main.hs b/driver/Main.hs
index 42b9986..5097a86 100644
--- a/driver/Main.hs
+++ b/driver/Main.hs
@@ -1,7 +1,29 @@
+{-# LANGUAGE ScopedTypeVariables #-}
module Main where
-import Documentation.Haddock (haddock)
-import System.Environment (getArgs)
+import Control.Exception
+import Documentation.Haddock (haddock)
+import System.Environment (getArgs)
+import System.Exit (exitFailure)
+import System.IO
main :: IO ()
-main = getArgs >>= haddock
+main = getArgs >>= expandResponse >>= haddock
+
+
+-- | Arguments which look like '@foo' will be replaced with the
+-- contents of file @foo at . The contents will be passed through 'words'
+-- and blanks filtered out first.
+--
+-- We quit if the file is not found or reading somehow fails.
+expandResponse :: [String] -> IO [String]
+expandResponse = fmap concat . mapM expand
+ where
+ expand :: String -> IO [String]
+ expand ('@':f) = readFileExc f >>= return . filter (not . null) . words
+ expand x = return [x]
+
+ readFileExc f =
+ readFile f `catch` \(e :: IOException) -> do
+ hPutStrLn stderr $ "Error while expanding response file: " ++ show e
+ exitFailure
More information about the ghc-commits
mailing list