module Distribution.Simple.Utils (
cabalVersion,
cabalBootstrapping,
die,
dieWithLocation,
warn, notice, setupMessage, info, debug,
chattyTry,
rawSystemExit,
rawSystemStdout,
rawSystemStdout',
maybeExit,
xargs,
smartCopySources,
createDirectoryIfMissingVerbose,
copyFileVerbose,
copyDirectoryRecursiveVerbose,
copyFiles,
currentDir,
findFile,
findFileWithExtension,
findFileWithExtension',
matchFileGlob,
matchDirFileGlob,
withTempFile,
withTempDirectory,
defaultPackageDesc,
findPackageDesc,
defaultHookedPackageDesc,
findHookedPackageDesc,
withFileContents,
writeFileAtomic,
rewriteFile,
fromUTF8,
toUTF8,
readUTF8File,
withUTF8FileContents,
writeUTF8File,
equating,
comparing,
isInfixOf,
intercalate,
lowercase,
wrapText,
wrapLine,
) where
import Control.Monad
( when, unless, filterM )
import Data.List
( nub, unfoldr, isPrefixOf, tails, intersperse )
import Data.Char as Char
( toLower, chr, ord )
import Data.Bits
( Bits((.|.), (.&.), shiftL, shiftR) )
import System.Directory
( getDirectoryContents, doesDirectoryExist, doesFileExist, removeFile
, copyFile )
import System.Environment
( getProgName )
import System.Cmd
( rawSystem )
import System.Exit
( exitWith, ExitCode(..) )
import System.FilePath
( normalise, (</>), (<.>), takeDirectory, splitFileName
, splitExtension, splitExtensions )
import System.Directory
( createDirectoryIfMissing, renameFile, removeDirectoryRecursive )
import System.IO
( Handle, openFile, openBinaryFile, IOMode(ReadMode), hSetBinaryMode
, hGetContents, stderr, stdout, hPutStr, hFlush, hClose )
import System.IO.Error as IO.Error
( try, isDoesNotExistError )
import qualified Control.Exception as Exception
import Distribution.Text
( display )
import Distribution.Package
( PackageIdentifier )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
(Version(..))
import Control.Exception (evaluate)
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent (forkIO)
import System.Process (runInteractiveProcess, waitForProcess)
#else
import System.Cmd (system)
import System.Directory (getTemporaryDirectory)
#endif
import Distribution.Compat.CopyFile
( copyOrdinaryFile )
import Distribution.Compat.TempFile (openTempFile,
openNewBinaryFile)
import Distribution.Compat.Exception (catchIO, onException)
#if mingw32_HOST_OS || mingw32_TARGET_OS
import Distribution.Compat.Exception (throwIOIO)
#endif
import Distribution.Verbosity
cabalVersion :: Version
#ifdef CABAL_VERSION
cabalVersion = Version [CABAL_VERSION] []
#else
cabalVersion = error "Cabal was not bootstrapped correctly"
#endif
cabalBootstrapping :: Bool
#ifdef CABAL_VERSION
cabalBootstrapping = False
#else
cabalBootstrapping = True
#endif
dieWithLocation :: FilePath -> Maybe Int -> String -> IO a
dieWithLocation filename lineno msg =
die $ normalise filename
++ maybe "" (\n -> ":" ++ show n) lineno
++ ": " ++ msg
die :: String -> IO a
die msg = do
hFlush stdout
pname <- getProgName
hPutStr stderr (wrapText (pname ++ ": " ++ msg))
exitWith (ExitFailure 1)
warn :: Verbosity -> String -> IO ()
warn verbosity msg =
when (verbosity >= normal) $ do
hFlush stdout
hPutStr stderr (wrapText ("Warning: " ++ msg))
notice :: Verbosity -> String -> IO ()
notice verbosity msg =
when (verbosity >= normal) $
putStr (wrapText msg)
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage verbosity msg pkgid =
notice verbosity (msg ++ ' ': display pkgid ++ "...")
info :: Verbosity -> String -> IO ()
info verbosity msg =
when (verbosity >= verbose) $
putStr (wrapText msg)
debug :: Verbosity -> String -> IO ()
debug verbosity msg =
when (verbosity >= deafening) $ do
putStr (wrapText msg)
hFlush stdout
chattyTry :: String
-> IO ()
-> IO ()
chattyTry desc action =
catchIO action $ \exception ->
putStrLn $ "Error while " ++ desc ++ ": " ++ show exception
wrapText :: String -> String
wrapText = unlines
. concatMap (map unwords
. wrapLine 79
. words)
. lines
wrapLine :: Int -> [String] -> [[String]]
wrapLine width = 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
hFlush stdout
exitcode <- rawSystem path args
unless (exitcode == ExitSuccess) $ do
debug verbosity $ path ++ " returned " ++ show exitcode
exitWith exitcode
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
#ifdef __GLASGOW_HASKELL__
Exception.bracket
(runInteractiveProcess path args Nothing Nothing)
(\(inh,outh,errh,_) -> hClose inh >> hClose outh >> hClose errh)
$ \(_,outh,errh,pid) -> do
hSetBinaryMode outh False
err <- hGetContents errh
forkIO $ do evaluate (length err); return ()
output <- hGetContents outh
evaluate (length output)
exitcode <- waitForProcess pid
unless (exitcode == ExitSuccess) $
debug verbosity $ path ++ " returned " ++ show exitcode
++ if null err then "" else
" with error message:\n" ++ err
return (output, exitcode)
#else
tmpDir <- getTemporaryDirectory
withTempFile tmpDir ".cmd.stdout" $ \tmpName tmpHandle -> do
hClose tmpHandle
let quote name = "'" ++ name ++ "'"
exitcode <- system $ unwords (map quote (path:args)) ++ " >" ++ quote tmpName
unless (exitcode == ExitSuccess) $
debug verbosity $ path ++ " returned " ++ show exitcode
withFileContents tmpName $ \output ->
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
findFile :: [FilePath]
-> FilePath
-> IO FilePath
findFile searchPath fileName =
findFirstFile id
[ path </> fileName
| path <- nub searchPath]
>>= maybe (die $ fileName ++ " doesn't exist") return
findFileWithExtension :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe FilePath)
findFileWithExtension extensions searchPath baseName =
findFirstFile id
[ path </> baseName <.> ext
| path <- nub searchPath
, ext <- nub extensions ]
findFileWithExtension' :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe (FilePath, FilePath))
findFileWithExtension' extensions searchPath baseName =
findFirstFile (uncurry (</>))
[ (path, baseName <.> ext)
| path <- nub searchPath
, ext <- nub extensions ]
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile file = findFirst
where findFirst [] = return Nothing
findFirst (x:xs) = do exists <- doesFileExist (file x)
if exists
then return (Just x)
else findFirst xs
data FileGlob
= NoGlob FilePath
| FileGlob FilePath String
parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions filepath of
(filepath', ext) -> case splitFileName filepath' of
(dir, "*") | '*' `elem` dir
|| '*' `elem` ext
|| null ext -> Nothing
| null dir -> Just (FileGlob "." ext)
| otherwise -> Just (FileGlob dir ext)
_ | '*' `elem` filepath -> Nothing
| otherwise -> Just (NoGlob filepath)
matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob "."
matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob filepath of
Nothing -> die $ "invalid file glob '" ++ filepath
++ "'. Wildcards '*' are only allowed in place of the file"
++ " name, not in the directory name or file extension."
++ " If a wildcard is used it must be with an file extension."
Just (NoGlob filepath') -> return [filepath']
Just (FileGlob dir' ext) -> do
files <- getDirectoryContents (dir </> dir')
case [ dir' </> file
| file <- files
, let (name, ext') = splitExtensions file
, not (null name) && ext' == ext ] of
[] -> die $ "filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return matches
smartCopySources :: Verbosity
-> [FilePath]
-> FilePath
-> [ModuleName]
-> [String]
-> IO ()
smartCopySources verbosity srcDirs targetDir sources searchSuffixes
= mapM moduleToFPErr sources >>= copyFiles verbosity targetDir
where moduleToFPErr m
= findFileWithExtension' searchSuffixes srcDirs (ModuleName.toFilePath m)
>>= maybe notFound return
where notFound = die $ "Error: Could not find module: " ++ display m
++ " with any suffix: " ++ show searchSuffixes
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)
copyOrdinaryFile src dest
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles verbosity targetDir srcFiles = do
let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles
mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs
sequence_ [ let src = srcBase </> srcFile
dest = targetDir </> srcFile
in info verbosity ("copy " ++ src ++ " to " ++ dest)
>> copyFile src dest
| (srcBase, srcFile) <- srcFiles ]
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
where getDirectoryContentsWithoutSpecial =
fmap (filter (not . flip elem [".", ".."]))
. getDirectoryContents
withTempFile :: FilePath
-> String
-> (FilePath -> Handle -> IO a) -> IO a
withTempFile tmpDir template action =
Exception.bracket
(openTempFile tmpDir template)
(\(name, handle) -> hClose handle >> removeFile name)
(uncurry action)
withTempDirectory :: Verbosity -> FilePath -> IO a -> IO a
withTempDirectory verbosity tmpDir =
Exception.bracket_
(createDirectoryIfMissingVerbose verbosity True tmpDir)
(removeDirectoryRecursive tmpDir)
withFileContents :: FilePath -> (String -> IO a) -> IO a
withFileContents name action =
Exception.bracket (openFile name ReadMode) hClose
(\hnd -> hGetContents hnd >>= action)
writeFileAtomic :: FilePath -> String -> IO ()
writeFileAtomic targetFile content = do
(tmpFile, tmpHandle) <- openNewBinaryFile targetDir template
do hPutStr tmpHandle content
hClose tmpHandle
#if mingw32_HOST_OS || mingw32_TARGET_OS
renameFile tmpFile targetFile
`catchIO` \err -> do
exists <- doesFileExist targetFile
if exists
then do removeFile targetFile
renameFile tmpFile targetFile
else throwIOIO err
#else
renameFile tmpFile targetFile
#endif
`onException` do hClose tmpHandle
removeFile tmpFile
where
template = targetName <.> "tmp"
targetDir | null targetDir_ = currentDir
| otherwise = targetDir_
(targetDir_,targetName) = splitFileName targetFile
rewriteFile :: FilePath -> String -> IO ()
rewriteFile path newContent =
flip catch mightNotExist $ do
existingContent <- readFile path
evaluate (length existingContent)
unless (existingContent == newContent) $
writeFileAtomic path newContent
where
mightNotExist e | isDoesNotExistError e = writeFileAtomic path newContent
| otherwise = ioError e
currentDir :: FilePath
currentDir = "."
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc _verbosity = findPackageDesc currentDir
findPackageDesc :: FilePath
-> IO FilePath
findPackageDesc dir
= do files <- getDirectoryContents dir
cabalFiles <- filterM doesFileExist
[ dir </> file
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == ".cabal" ]
case cabalFiles of
[] -> noDesc
[cabalFile] -> return cabalFile
multiple -> multiDesc multiple
where
noDesc :: IO a
noDesc = die $ "No cabal file found.\n"
++ "Please create a package description file <pkgname>.cabal"
multiDesc :: [String] -> IO a
multiDesc l = die $ "Multiple cabal files found.\n"
++ "Please use only one of: "
++ show l
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = findHookedPackageDesc currentDir
findHookedPackageDesc
:: FilePath
-> IO (Maybe FilePath)
findHookedPackageDesc dir = do
files <- getDirectoryContents dir
buildInfoFiles <- filterM doesFileExist
[ dir </> file
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == buildInfoExt ]
case buildInfoFiles of
[] -> return Nothing
[f] -> return (Just f)
_ -> die ("Multiple files with extension " ++ buildInfoExt)
buildInfoExt :: String
buildInfoExt = ".buildinfo"
fromUTF8 :: String -> String
fromUTF8 [] = []
fromUTF8 (c:cs)
| c <= '\x7F' = c : fromUTF8 cs
| c <= '\xBF' = replacementChar : fromUTF8 cs
| c <= '\xDF' = twoBytes c cs
| c <= '\xEF' = moreBytes 3 0x800 cs (ord c .&. 0xF)
| c <= '\xF7' = moreBytes 4 0x10000 cs (ord c .&. 0x7)
| c <= '\xFB' = moreBytes 5 0x200000 cs (ord c .&. 0x3)
| c <= '\xFD' = moreBytes 6 0x4000000 cs (ord c .&. 0x1)
| otherwise = replacementChar : fromUTF8 cs
where
twoBytes c0 (c1:cs')
| ord c1 .&. 0xC0 == 0x80
= let d = ((ord c0 .&. 0x1F) `shiftL` 6)
.|. (ord c1 .&. 0x3F)
in if d >= 0x80
then chr d : fromUTF8 cs'
else replacementChar : fromUTF8 cs'
twoBytes _ cs' = replacementChar : fromUTF8 cs'
moreBytes :: Int -> Int -> [Char] -> Int -> [Char]
moreBytes 1 overlong cs' acc
| overlong <= acc && acc <= 0x10FFFF
&& (acc < 0xD800 || 0xDFFF < acc)
&& (acc < 0xFFFE || 0xFFFF < acc)
= chr acc : fromUTF8 cs'
| otherwise
= replacementChar : fromUTF8 cs'
moreBytes byteCount overlong (cn:cs') acc
| ord cn .&. 0xC0 == 0x80
= moreBytes (byteCount1) overlong cs'
((acc `shiftL` 6) .|. ord cn .&. 0x3F)
moreBytes _ _ cs' _
= replacementChar : fromUTF8 cs'
replacementChar = '\xfffd'
toUTF8 :: String -> String
toUTF8 [] = []
toUTF8 (c:cs)
| c <= '\x07F' = c
: toUTF8 cs
| c <= '\x7FF' = chr (0xC0 .|. (w `shiftR` 6))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
| c <= '\xFFFF'= chr (0xE0 .|. (w `shiftR` 12))
: chr (0x80 .|. ((w `shiftR` 6) .&. 0x3F))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
| otherwise = chr (0xf0 .|. (w `shiftR` 18))
: chr (0x80 .|. ((w `shiftR` 12) .&. 0x3F))
: chr (0x80 .|. ((w `shiftR` 6) .&. 0x3F))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
where w = ord c
readUTF8File :: FilePath -> IO String
readUTF8File f = fmap fromUTF8 . hGetContents =<< openBinaryFile f ReadMode
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
withUTF8FileContents name action =
Exception.bracket (openBinaryFile name ReadMode) hClose
(\hnd -> hGetContents hnd >>= action . fromUTF8)
writeUTF8File :: FilePath -> String -> IO ()
writeUTF8File path = writeFileAtomic path . toUTF8
equating :: Eq a => (b -> a) -> b -> b -> Bool
equating p x y = p x == p y
comparing :: Ord a => (b -> a) -> b -> b -> Ordering
comparing p x y = p x `compare` p y
isInfixOf :: String -> String -> Bool
isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
intercalate :: [a] -> [[a]] -> [a]
intercalate sep = concat . intersperse sep
lowercase :: String -> String
lowercase = map Char.toLower