module Distribution.Simple.Utils (
die,
dieWithLocation,
warn, notice, info, debug,
breaks,
wrapText,
rawSystemExit,
rawSystemStdout,
rawSystemStdout',
maybeExit,
xargs,
matchesDescFile,
rawSystemPathExit,
smartCopySources,
createDirectoryIfMissingVerbose,
copyFileVerbose,
copyDirectoryRecursiveVerbose,
moduleToFilePath,
moduleToFilePath2,
mkLibName,
mkProfLibName,
mkSharedLibName,
currentDir,
dotToSep,
findFile,
defaultPackageDesc,
findPackageDesc,
defaultHookedPackageDesc,
findHookedPackageDesc,
exeExtension,
objExtension,
dllExtension,
#ifdef DEBUG
hunitTests
#endif
) where
#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 604
#if __GLASGOW_HASKELL__ < 603
#include "config.h"
#else
#include "ghcconfig.h"
#endif
#endif
import Control.Monad
( when, filterM, unless, liftM2 )
import Data.List
( nub, unfoldr )
import System.Directory
( getDirectoryContents, getCurrentDirectory, doesDirectoryExist
, doesFileExist, removeFile )
import System.Environment
( getProgName )
import System.Exit
( exitWith, ExitCode(..) )
import System.FilePath
( takeDirectory, takeExtension, (</>), (<.>), pathSeparator )
import System.IO
( hPutStrLn, stderr, hFlush, stdout, openFile, IOMode(WriteMode) )
import System.IO.Error
( try )
import Distribution.Compat.Directory
( copyFile, findExecutable, createDirectoryIfMissing
, getDirectoryContentsWithoutSpecial)
import Distribution.Compat.RawSystem
( rawSystem )
import Distribution.Compat.Exception
( bracket )
import Distribution.System
( OS(..), os )
import Distribution.Version
(showVersion)
import Distribution.Package
(PackageIdentifier(..))
#if __GLASGOW_HASKELL__ >= 604
import Control.Exception (evaluate)
import System.Process (runProcess, waitForProcess)
#else
import System.Cmd (system)
#endif
import System.IO (hClose)
#if __GLASGOW_HASKELL__ >= 604
import Distribution.Compat.TempFile (openTempFile)
#else
import Distribution.Compat.TempFile (withTempFile)
#endif
import Distribution.Verbosity
#ifdef DEBUG
import Test.HUnit ((~:), (~=?), Test(..), assertEqual)
#endif
dieWithLocation :: FilePath -> (Maybe Int) -> String -> IO a
dieWithLocation fname Nothing msg = die (fname ++ ": " ++ msg)
dieWithLocation fname (Just n) msg = die (fname ++ ":" ++ show n ++ ": " ++ msg)
die :: String -> IO a
die msg = do
hFlush stdout
pname <- getProgName
hPutStrLn stderr (pname ++ ": " ++ msg)
exitWith (ExitFailure 1)
warn :: Verbosity -> String -> IO ()
warn verbosity msg =
when (verbosity >= normal) $ do
hFlush stdout
hPutStrLn stderr ("Warning: " ++ msg)
notice :: Verbosity -> String -> IO ()
notice verbosity msg =
when (verbosity >= normal) $
putStrLn msg
info :: Verbosity -> String -> IO ()
info verbosity msg =
when (verbosity >= verbose) $
putStrLn msg
debug :: Verbosity -> String -> IO ()
debug verbosity msg =
when (verbosity >= deafening) $
putStrLn msg
breaks :: (a -> Bool) -> [a] -> [[a]]
breaks _ [] = []
breaks f xs = case span f xs of
(_, xs') ->
case break f xs' of
(v, xs'') ->
v : breaks f xs''
wrapText :: Int -> [String] -> [String]
wrapText width = map unwords . wrap 0 []
where wrap :: Int -> [String] -> [String] -> [[String]]
wrap 0 [] (w:ws)
| length w + 1 > width
= wrap (length w) [w] ws
wrap col line (w:ws)
| col + length w + 1 > width
= reverse line : wrap 0 [] (w:ws)
wrap col line (w:ws)
= let col' = col + length w + 1
in wrap col' (w:line) ws
wrap _ [] [] = []
wrap _ line [] = [reverse line]
maybeExit :: IO ExitCode -> IO ()
maybeExit cmd = do
res <- cmd
unless (res == ExitSuccess) $ exitWith res
printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
printRawCommandAndArgs verbosity path args
| verbosity >= deafening = print (path, args)
| verbosity >= verbose = putStrLn $ unwords (path : args)
| otherwise = return ()
rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()
rawSystemExit verbosity path args = do
printRawCommandAndArgs verbosity path args
maybeExit $ rawSystem path args
rawSystemPathExit :: Verbosity -> String -> [String] -> IO ()
rawSystemPathExit verbosity prog args = do
r <- findExecutable prog
case r of
Nothing -> die ("Cannot find: " ++ prog)
Just path -> rawSystemExit verbosity path args
rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String
rawSystemStdout verbosity path args = do
(output, exitCode) <- rawSystemStdout' verbosity path args
unless (exitCode == ExitSuccess) $ exitWith exitCode
return output
rawSystemStdout' :: Verbosity -> FilePath -> [String] -> IO (String, ExitCode)
rawSystemStdout' verbosity path args = do
printRawCommandAndArgs verbosity path args
#if __GLASGOW_HASKELL__ >= 604
bracket (liftM2 (,) (openTempFile "." "tmp") (openFile devNull WriteMode))
(\((tmpName, tmpHandle), nullHandle) -> do
hClose tmpHandle
removeFile tmpName
hClose nullHandle)
$ \((tmpName, tmpHandle), nullHandle) -> do
cmdHandle <- runProcess path args Nothing Nothing
Nothing (Just tmpHandle) (Just nullHandle)
exitCode <- waitForProcess cmdHandle
output <- readFile tmpName
evaluate (length output)
return (output, exitCode)
#else
withTempFile "." "" $ \tmpName -> do
let quote name = "'" ++ name ++ "'"
exitCode <- system $ unwords (map quote (path:args)) ++ " >" ++ quote tmpName
output <- readFile tmpName
length output `seq` return (output, exitCode)
#endif
xargs :: Int -> ([String] -> IO ())
-> [String] -> [String] -> IO ()
xargs maxSize rawSystemFun fixedArgs bigArgs =
let fixedArgSize = sum (map length fixedArgs) + length fixedArgs
chunkSize = maxSize fixedArgSize
in mapM_ (rawSystemFun . (fixedArgs ++)) (chunks chunkSize bigArgs)
where chunks len = unfoldr $ \s ->
if null s then Nothing
else Just (chunk [] len s)
chunk acc _ [] = (reverse acc,[])
chunk acc len (s:ss)
| len' < len = chunk (s:acc) (lenlen'1) ss
| otherwise = (reverse acc, s:ss)
where len' = length s
moduleToFilePath :: [FilePath]
-> String
-> [String]
-> IO [FilePath]
moduleToFilePath pref s possibleSuffixes
= filterM doesFileExist $
concatMap (searchModuleToPossiblePaths s possibleSuffixes) pref
where searchModuleToPossiblePaths :: String -> [String] -> FilePath -> [FilePath]
searchModuleToPossiblePaths s' suffs searchP
= moduleToPossiblePaths searchP s' suffs
moduleToFilePath2
:: [FilePath]
-> String
-> [String]
-> IO [(FilePath, FilePath)]
moduleToFilePath2 locs mname possibleSuffixes
= filterM exists $
[(loc, fname <.> ext) | loc <- locs, ext <- possibleSuffixes]
where
fname = dotToSep mname
exists (loc, relname) = doesFileExist (loc </> relname)
moduleToPossiblePaths :: FilePath
-> String
-> [String]
-> [FilePath]
moduleToPossiblePaths searchPref s possibleSuffixes =
let fname = searchPref </> (dotToSep s)
in [fname <.> ext | ext <- possibleSuffixes]
findFile :: [FilePath]
-> FilePath
-> IO FilePath
findFile prefPathsIn locPath = do
let prefPaths = nub prefPathsIn
paths <- filterM doesFileExist [prefPath </> locPath | prefPath <- prefPaths]
case nub paths of
[path] -> return path
[] -> die (locPath ++ " doesn't exist")
paths' -> die (locPath ++ " is found in multiple places:" ++ unlines (map ((++) " ") paths'))
dotToSep :: String -> String
dotToSep = map dts
where
dts '.' = pathSeparator
dts c = c
smartCopySources :: Verbosity
-> [FilePath]
-> FilePath
-> [String]
-> [String]
-> Bool
-> Bool
-> IO ()
smartCopySources verbosity srcDirs targetDir sources searchSuffixes exitIfNone preserveDirs
= do createDirectoryIfMissingVerbose verbosity True targetDir
allLocations <- mapM moduleToFPErr sources
let copies = [(srcDir </> name,
if preserveDirs
then targetDir </> srcDir </> name
else targetDir </> name) |
(srcDir, name) <- concat allLocations]
mapM_ (createDirectoryIfMissingVerbose verbosity True) $ nub $
[takeDirectory targetFile | (_, targetFile) <- copies]
sequence_ [copyFileVerbose verbosity srcFile destFile |
(srcFile, destFile) <- copies]
where moduleToFPErr m
= do p <- moduleToFilePath2 srcDirs m searchSuffixes
when (null p && exitIfNone)
(die ("Error: Could not find module: " ++ m
++ " with any suffix: " ++ (show searchSuffixes)))
return p
createDirectoryIfMissingVerbose :: Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose verbosity parentsToo dir = do
let msgParents = if parentsToo then " (and its parents)" else ""
info verbosity ("Creating " ++ dir ++ msgParents)
createDirectoryIfMissing parentsToo dir
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose verbosity src dest = do
info verbosity ("copy " ++ src ++ " to " ++ dest)
copyFile src dest
copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursiveVerbose verbosity srcDir destDir = do
info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
let aux src dest =
let cp :: FilePath -> IO ()
cp f = let srcFile = src </> f
destFile = dest </> f
in do success <- try (copyFileVerbose verbosity srcFile destFile)
case success of
Left e -> do isDir <- doesDirectoryExist srcFile
unless isDir $ ioError e
aux srcFile destFile
Right _ -> return ()
in do createDirectoryIfMissingVerbose verbosity False dest
getDirectoryContentsWithoutSpecial src >>= mapM_ cp
in aux srcDir destDir
currentDir :: FilePath
currentDir = "."
mkLibName :: FilePath
-> String
-> String
mkLibName pref lib = pref </> ("libHS" ++ lib ++ ".a")
mkProfLibName :: FilePath
-> String
-> String
mkProfLibName pref lib = mkLibName pref (lib++"_p")
mkSharedLibName :: FilePath
-> String
-> PackageIdentifier
-> String
mkSharedLibName pref lib (PackageIdentifier compilerName compilerVersion)
= pref </> ("libHS" ++ lib ++ "-" ++ compiler) <.> dllExtension
where compiler = compilerName ++ showVersion compilerVersion
oldDescFile :: String
oldDescFile = "Setup.description"
cabalExt :: String
cabalExt = "cabal"
buildInfoExt :: String
buildInfoExt = "buildinfo"
matchesDescFile :: FilePath -> Bool
matchesDescFile p = (takeExtension p) == '.':cabalExt
|| p == oldDescFile
noDesc :: IO a
noDesc = die $ "No description file found, please create a cabal-formatted description file with the name <pkgname>." ++ cabalExt
multiDesc :: [String] -> IO a
multiDesc l = die $ "Multiple description files found. Please use only one of : "
++ show (filter (/= oldDescFile) l)
descriptionCheck :: Verbosity -> [FilePath] -> IO FilePath
descriptionCheck _ [] = noDesc
descriptionCheck verbosity [x]
| x == oldDescFile
= do warn verbosity $ "The filename \"Setup.description\" is deprecated, please move to <pkgname>." ++ cabalExt
return x
| matchesDescFile x = return x
| otherwise = noDesc
descriptionCheck verbosity [x,y]
| x == oldDescFile
= do warn verbosity $ "The filename \"Setup.description\" is deprecated. Please move out of the way. Using \""
++ y ++ "\""
return y
| y == oldDescFile
= do warn verbosity $ "The filename \"Setup.description\" is deprecated. Please move out of the way. Using \""
++ x ++ "\""
return x
| otherwise = multiDesc [x,y]
descriptionCheck _ l = multiDesc l
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc verbosity
= getCurrentDirectory >>= findPackageDesc verbosity
findPackageDesc :: Verbosity
-> FilePath
-> IO FilePath
findPackageDesc verbosity p
= do ls <- getDirectoryContents p
let descs = filter matchesDescFile ls
descriptionCheck verbosity descs
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = getCurrentDirectory >>= findHookedPackageDesc
findHookedPackageDesc
:: FilePath
-> IO (Maybe FilePath)
findHookedPackageDesc dir = do
ns <- getDirectoryContents dir
case [dir </> n |
n <- ns, takeExtension n == '.':buildInfoExt] of
[] -> return Nothing
[f] -> return (Just f)
_ -> die ("Multiple files with extension " ++ buildInfoExt)
exeExtension :: String
exeExtension = case os of
Windows _ -> "exe"
_ -> ""
objExtension :: String
objExtension = "o"
dllExtension :: String
dllExtension = case os of
Windows _ -> "dll"
OSX -> "dylib"
_ -> "so"
devNull :: FilePath
devNull = case os of
Windows _ -> "NUL"
_ -> "/dev/null"
#ifdef DEBUG
hunitTests :: [Test]
hunitTests
= let suffixes = ["hs", "lhs"]
in [TestCase $
do mp1 <- moduleToFilePath [""] "Distribution.Simple.Build" suffixes --exists
mp2 <- moduleToFilePath [""] "Foo.Bar" suffixes
assertEqual "existing not found failed"
["Distribution" </> "Simple" </> "Build.hs"] mp1
assertEqual "not existing not nothing failed" [] mp2,
"moduleToPossiblePaths 1" ~: "failed" ~:
["Foo" </> "Bar" </> "Bang.hs","Foo" </> "Bar" </> "Bang.lhs"]
~=? (moduleToPossiblePaths "" "Foo.Bar.Bang" suffixes),
"moduleToPossiblePaths2 " ~: "failed" ~:
(moduleToPossiblePaths "" "Foo" suffixes) ~=? ["Foo.hs", "Foo.lhs"],
TestCase (do files <- filesWithExtensions "." "cabal"
assertEqual "filesWithExtensions" "Cabal.cabal" (head files))
]
filesWithExtensions :: FilePath
-> String
-> IO [FilePath]
filesWithExtensions dir extension
= do allFiles <- getDirectoryContents dir
return $ filter hasExt allFiles
where
hasExt f = takeExtension f == '.':extension
#endif