[commit: packages/Cabal] ghc-head: Actually implement the '--list-sources' option of 'cabal sdist'. (b915e0c)
git at git.haskell.org
git at git.haskell.org
Mon Aug 26 23:23:55 CEST 2013
Repository : ssh://git@git.haskell.org/Cabal
On branch : ghc-head
Link : http://git.haskell.org/?p=packages/Cabal.git;a=commit;h=b915e0c09cbc1e199b4ec019dc1be95caf728e06
>---------------------------------------------------------------
commit b915e0c09cbc1e199b4ec019dc1be95caf728e06
Author: Mikhail Glushenkov <the.dead.shall.rise at gmail.com>
Date: Wed May 1 16:52:28 2013 +0200
Actually implement the '--list-sources' option of 'cabal sdist'.
>---------------------------------------------------------------
b915e0c09cbc1e199b4ec019dc1be95caf728e06
Cabal/Distribution/Simple/SrcDist.hs | 55 ++++++++++++++++++++--------------
1 file changed, 32 insertions(+), 23 deletions(-)
diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs
index 797f1e2..06f77d9 100644
--- a/Cabal/Distribution/Simple/SrcDist.hs
+++ b/Cabal/Distribution/Simple/SrcDist.hs
@@ -92,7 +92,8 @@ import Distribution.Simple.Utils
, findFile, findFileWithExtension, matchFileGlob
, withTempDirectory, defaultPackageDesc
, die, warn, notice, setupMessage )
-import Distribution.Simple.Setup (SDistFlags(..), fromFlag, flagToMaybe)
+import Distribution.Simple.Setup ( Flag(..), SDistFlags(..)
+ , fromFlag, flagToMaybe)
import Distribution.Simple.PreProcess ( PPSuffixHandler, ppSuffixes
, preprocessComponent )
import Distribution.Simple.LocalBuildInfo
@@ -109,6 +110,7 @@ import Data.List (partition, isPrefixOf)
import Data.Maybe (isNothing, catMaybes)
import Data.Time (UTCTime, getCurrentTime, toGregorian, utctDay)
import System.Directory ( doesFileExist )
+import System.IO (IOMode(WriteMode), hPutStrLn, withFile)
import Distribution.Verbosity (Verbosity)
import System.FilePath
( (</>), (<.>), dropExtension, isAbsolute )
@@ -135,28 +137,35 @@ sdistWith :: PackageDescription -- ^information from the tarball
-> IO ()
sdistWith pkg mb_lbi flags mkTmpDir pps createArchiveFun = do
- -- do some QA
- printPackageProblems verbosity pkg
-
- when (isNothing mb_lbi) $
- warn verbosity "Cannot run preprocessors. Run 'configure' command first."
-
- date <- getCurrentTime
- let pkg' | snapshot = snapshotPackage date pkg
- | otherwise = pkg
-
- case flagToMaybe (sDistDirectory flags) of
- Just targetDir -> do
- generateSourceDir targetDir pkg'
- notice verbosity $ "Source directory created: " ++ targetDir
-
- Nothing -> do
- createDirectoryIfMissingVerbose verbosity True tmpTargetDir
- withTempDirectory verbosity False tmpTargetDir "sdist." $ \tmpDir -> do
- let targetDir = tmpDir </> tarBallName pkg'
- generateSourceDir targetDir pkg'
- targzFile <- createArchiveFun verbosity pkg' mb_lbi tmpDir targetPref
- notice verbosity $ "Source tarball created: " ++ targzFile
+ -- When given --list-sources, just output the list of sources to a file.
+ case (sDistListSources flags) of
+ Flag path -> withFile path WriteMode $ \outHandle -> do
+ (ordinary, maybeExecutable) <- listPackageSources verbosity pkg pps
+ mapM_ (hPutStrLn outHandle) ordinary
+ mapM_ (hPutStrLn outHandle) maybeExecutable
+ NoFlag -> do
+ -- do some QA
+ printPackageProblems verbosity pkg
+
+ when (isNothing mb_lbi) $
+ warn verbosity "Cannot run preprocessors. Run 'configure' command first."
+
+ date <- getCurrentTime
+ let pkg' | snapshot = snapshotPackage date pkg
+ | otherwise = pkg
+
+ case flagToMaybe (sDistDirectory flags) of
+ Just targetDir -> do
+ generateSourceDir targetDir pkg'
+ notice verbosity $ "Source directory created: " ++ targetDir
+
+ Nothing -> do
+ createDirectoryIfMissingVerbose verbosity True tmpTargetDir
+ withTempDirectory verbosity False tmpTargetDir "sdist." $ \tmpDir -> do
+ let targetDir = tmpDir </> tarBallName pkg'
+ generateSourceDir targetDir pkg'
+ targzFile <- createArchiveFun verbosity pkg' mb_lbi tmpDir targetPref
+ notice verbosity $ "Source tarball created: " ++ targzFile
where
generateSourceDir targetDir pkg' = do
More information about the ghc-commits
mailing list