module Distribution.Simple.Utils (
cabalVersion,
die,
dieWithLocation,
topHandler,
warn, notice, setupMessage, info, debug,
chattyTry,
rawSystemExit,
rawSystemExitWithEnv,
rawSystemStdout,
rawSystemStdInOut,
maybeExit,
xargs,
findProgramLocation,
findProgramVersion,
smartCopySources,
createDirectoryIfMissingVerbose,
copyFileVerbose,
copyDirectoryRecursiveVerbose,
copyFiles,
installOrdinaryFile,
installExecutableFile,
installOrdinaryFiles,
installDirectoryContents,
setFileOrdinary,
setFileExecutable,
currentDir,
findFile,
findFirstFile,
findFileWithExtension,
findFileWithExtension',
findModuleFile,
findModuleFiles,
getDirectoryContentsRecursive,
matchFileGlob,
matchDirFileGlob,
parseFileGlob,
FileGlob(..),
withTempFile,
withTempDirectory,
defaultPackageDesc,
findPackageDesc,
defaultHookedPackageDesc,
findHookedPackageDesc,
withFileContents,
writeFileAtomic,
rewriteFile,
fromUTF8,
toUTF8,
readUTF8File,
withUTF8FileContents,
writeUTF8File,
normaliseLineEndings,
equating,
comparing,
isInfixOf,
intercalate,
lowercase,
wrapText,
wrapLine,
) where
import Control.Monad
( when, unless, filterM )
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent.MVar
( newEmptyMVar, putMVar, takeMVar )
#endif
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
, findExecutable )
import System.Environment
( getProgName )
import System.Cmd
( rawSystem )
import System.Exit
( exitWith, ExitCode(..) )
import System.FilePath
( normalise, (</>), (<.>), takeDirectory, splitFileName
, splitExtension, splitExtensions, splitDirectories )
import System.Directory
( createDirectory, renameFile, removeDirectoryRecursive )
import System.IO
( Handle, openFile, openBinaryFile, IOMode(ReadMode), hSetBinaryMode
, hGetContents, stderr, stdout, hPutStr, hFlush, hClose )
import System.IO.Error as IO.Error
( isDoesNotExistError, isAlreadyExistsError
, ioeSetFileName, ioeGetFileName, ioeGetErrorString )
#if !(defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608))
import System.IO.Error
( ioeSetLocation, ioeGetLocation )
#endif
import System.IO.Unsafe
( unsafeInterleaveIO )
import qualified Control.Exception as Exception
import Distribution.Text
( display, simpleParse )
import Distribution.Package
( PackageIdentifier )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
(Version(..))
import Control.Exception (evaluate)
import System.Process (runProcess)
#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
( copyFile, copyOrdinaryFile, copyExecutableFile
, setFileOrdinary, setFileExecutable, setDirOrdinary )
import Distribution.Compat.TempFile
( openTempFile, openNewBinaryFile, createTempDirectory )
import Distribution.Compat.Exception
( IOException, throwIOIO, tryIO, catchIO, catchExit, onException )
import Distribution.Verbosity
#ifdef VERSION_base
import qualified Paths_Cabal (version)
#endif
cabalVersion :: Version
#if defined(VERSION_base)
cabalVersion = version :: VersionPaths_Cabal.version
#elif defined(CABAL_VERSION)
cabalVersion = Version [CABAL_VERSION] []
#else
cabalVersion = Version [1,9999] []
#endif
dieWithLocation :: FilePath -> Maybe Int -> String -> IO a
dieWithLocation filename lineno msg =
ioError :: IOError -> IO aioError (.) :: (b -> c) -> (a -> b) -> a -> c. setLocation :: Maybe a -> IOError -> IOErrorsetLocation lineno :: Maybe Intlineno
(.) :: (b -> c) -> (a -> b) -> a -> c. flip :: (a -> b -> c) -> b -> a -> cflip ioeSetFileName :: IOError -> FilePath -> IOErrorioeSetFileName (normalise :: FilePath -> FilePathnormalise filename :: FilePathfilename)
($) :: (a -> b) -> a -> b$ userError :: String -> IOErroruserError msg :: Stringmsg
where
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
setLocation _ err = err
#else
setLocation Nothing err = err :: IOErrorerr
setLocation (Just n) err = ioeSetLocation :: IOError -> String -> IOErrorioeSetLocation err :: IOErrorerr (show :: Show a => a -> Stringshow n :: an)
#endif
die :: String -> IO a
die msg = ioError :: IOError -> IO aioError (userError :: String -> IOErroruserError msg :: Stringmsg)
topHandler :: IO a -> IO a
topHandler prog = catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO prog :: IO aprog handle :: IOError -> IO bhandle
where
handle ioe = do
hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
pname <- getProgName :: IO StringgetProgName
hPutStr :: Handle -> String -> IO ()hPutStr stderr :: Handlestderr (mesage :: [Char] -> Stringmesage pname :: [Char]pname)
exitWith :: ExitCode -> IO aexitWith (ExitFailure :: Int -> ExitCodeExitFailure 1)
where
mesage pname = wrapText :: String -> StringwrapText (pname :: [Char]pname (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ file :: FilePathfile (++) :: [a] -> [a] -> [a]++ detail :: Stringdetail)
file = case ioeGetFileName :: IOError -> Maybe FilePathioeGetFileName ioe :: IOErrorioe of
Nothing -> ""
Just path -> path :: FilePathpath (++) :: [a] -> [a] -> [a]++ location :: [Char]location (++) :: [a] -> [a] -> [a]++ ": "
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
location = ""
#else
location = case ioeGetLocation :: IOError -> StringioeGetLocation ioe :: IOErrorioe of
l@(n:_) | n :: an (>=) :: Ord a => a -> a -> Bool>= '0' (&&) :: Bool -> Bool -> Bool&& n :: an (<=) :: Ord a => a -> a -> Bool<= '9' -> ':' (:) :: a -> [a] -> [a]: l :: [String]l
_ -> ""
#endif
detail = ioeGetErrorString :: IOError -> StringioeGetErrorString ioe :: IOErrorioe
warn :: Verbosity -> String -> IO ()
warn verbosity msg =
when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= normal :: Verbositynormal) ($) :: (a -> b) -> a -> b$ do
hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
hPutStr :: Handle -> String -> IO ()hPutStr stderr :: Handlestderr (wrapText :: String -> StringwrapText ("Warning: " (++) :: [a] -> [a] -> [a]++ msg :: Stringmsg))
notice :: Verbosity -> String -> IO ()
notice verbosity msg =
when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= normal :: Verbositynormal) ($) :: (a -> b) -> a -> b$
putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage verbosity msg pkgid =
notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity (msg :: Stringmsg (++) :: [a] -> [a] -> [a]++ ' '(:) :: a -> [a] -> [a]: display :: Text a => a -> Stringdisplay pkgid :: PackageIdentifierpkgid (++) :: [a] -> [a] -> [a]++ "...")
info :: Verbosity -> String -> IO ()
info verbosity msg =
when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose) ($) :: (a -> b) -> a -> b$
putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)
debug :: Verbosity -> String -> IO ()
debug verbosity msg =
when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening) ($) :: (a -> b) -> a -> b$ do
putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)
hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
chattyTry :: String
-> IO ()
-> IO ()
chattyTry desc action =
catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO action :: IO ()action ($) :: (a -> b) -> a -> b$ \exception ->
putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ "Error while " (++) :: [a] -> [a] -> [a]++ desc :: Stringdesc (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exception :: IOExceptionexception
wrapText :: String -> String
wrapText = unlines :: [String] -> Stringunlines
(.) :: (b -> c) -> (a -> b) -> a -> c. concatMap :: (a -> [b]) -> [a] -> [b]concatMap (map :: (a -> b) -> [a] -> [b]map unwords :: [String] -> Stringunwords
(.) :: (b -> c) -> (a -> b) -> a -> c. wrapLine :: Int -> [String] -> [[String]]wrapLine 79
(.) :: (b -> c) -> (a -> b) -> a -> c. words :: String -> [String]words)
(.) :: (b -> c) -> (a -> b) -> a -> c. lines :: String -> [String]lines
wrapLine :: Int -> [String] -> [[String]]
wrapLine width = wrap :: Int -> [String] -> [String] -> [[String]]wrap 0 [] :: [a][]
where wrap :: Int -> [String] -> [String] -> [[String]]
wrap 0 [] (w:ws)
| length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1 (>) :: Ord a => a -> a -> Bool> width :: Intwidth
= wrap :: Int -> [String] -> [String] -> [[String]]wrap (length :: [a] -> Intlength w :: Stringw) [w :: Stringw] ws :: [String]ws
wrap col line (w:ws)
| col :: Intcol (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1 (>) :: Ord a => a -> a -> Bool> width :: Intwidth
= reverse :: [a] -> [a]reverse line :: [String]line (:) :: a -> [a] -> [a]: wrap :: Int -> [String] -> [String] -> [[String]]wrap 0 [] :: [a][] (w :: Stringw(:) :: a -> [a] -> [a]:ws :: [String]ws)
wrap col line (w:ws)
= let col' = col :: Intcol (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1
in wrap :: Int -> [String] -> [String] -> [[String]]wrap col' :: Intcol' (w :: Stringw(:) :: a -> [a] -> [a]:line :: [String]line) ws :: [String]ws
wrap _ [] [] = [] :: [a][]
wrap _ line [] = [reverse :: [a] -> [a]reverse line :: [String]line]
maybeExit :: IO ExitCode -> IO ()
maybeExit cmd = do
res <- cmd :: IO ExitCodecmd
unless :: Monad m => Bool -> m () -> m ()unless (res :: Maybe FilePathres (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ exitWith :: ExitCode -> IO aexitWith res :: Maybe FilePathres
printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
printRawCommandAndArgs verbosity path args
| verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening = print :: Show a => a -> IO ()print (path :: FilePathpath, args :: [String]args)
| verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ unwords :: [String] -> Stringunwords (path :: FilePathpath (:) :: a -> [a] -> [a]: args :: [String]args)
| otherwise :: Boolotherwise = return :: Monad m => forall a. a -> m areturn ()
printRawCommandAndArgsAndEnv :: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
printRawCommandAndArgsAndEnv verbosity path args env
| verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening = do putStrLn :: String -> IO ()putStrLn ("Environment: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow env :: [(String, String)]env)
print :: Show a => a -> IO ()print (path :: FilePathpath, args :: [String]args)
| verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ unwords :: [String] -> Stringunwords (path :: FilePathpath (:) :: a -> [a] -> [a]: args :: [String]args)
| otherwise :: Boolotherwise = return :: Monad m => forall a. a -> m areturn ()
rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()
rawSystemExit verbosity path args = do
printRawCommandAndArgs ::
Verbosity -> FilePath -> [String] -> IO ()printRawCommandAndArgs verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args
hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
exitcode <- rawSystem :: String -> [String] -> IO ExitCoderawSystem path :: FilePathpath args :: [String]args
unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ do
debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
exitWith :: ExitCode -> IO aexitWith exitcode :: ExitCodeexitcode
rawSystemExitWithEnv :: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnv verbosity path args env = do
printRawCommandAndArgsAndEnv ::
Verbosity -> FilePath -> [String] -> [(String, String)] -> IO ()printRawCommandAndArgsAndEnv verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args env :: [(String, String)]env
hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
ph <- runProcess ::
FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ProcessHandlerunProcess path :: FilePathpath args :: [String]args Nothing :: Maybe aNothing (Just :: a -> Maybe aJust env :: [(String, String)]env) Nothing :: Maybe aNothing Nothing :: Maybe aNothing Nothing :: Maybe aNothing
exitcode <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess ph :: ProcessHandleph
unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ do
debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
exitWith :: ExitCode -> IO aexitWith exitcode :: ExitCodeexitcode
rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String
rawSystemStdout verbosity path args = do
(output, errors, exitCode) <- rawSystemStdInOut ::
Verbosity
-> FilePath
-> [String]
-> Maybe (String, Bool)
-> Bool
-> IO (String, String, ExitCode)rawSystemStdInOut verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args
Nothing :: Maybe aNothing False :: BoolFalse
when :: Monad m => Bool -> m () -> m ()when (exitCode :: ExitCodeexitCode (/=) :: Eq a => a -> a -> Bool/= ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$
die :: String -> IO adie errors :: Stringerrors
return :: Monad m => forall a. a -> m areturn output :: Stringoutput
rawSystemStdInOut :: Verbosity
-> FilePath -> [String]
-> Maybe (String, Bool)
-> Bool
-> IO (String, String, ExitCode)
rawSystemStdInOut verbosity path args input outputBinary = do
printRawCommandAndArgs ::
Verbosity -> FilePath -> [String] -> IO ()printRawCommandAndArgs verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args
#ifdef __GLASGOW_HASKELL__
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
(runInteractiveProcess ::
FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> IO (Handle, Handle, Handle, ProcessHandle)runInteractiveProcess path :: FilePathpath args :: [String]args Nothing :: Maybe aNothing Nothing :: Maybe aNothing)
(\(inh,outh,errh,_) -> hClose :: Handle -> IO ()hClose inh :: Handleinh (>>) :: Monad m => forall a b. m a -> m b -> m b>> hClose :: Handle -> IO ()hClose outh :: Handleouth (>>) :: Monad m => forall a b. m a -> m b -> m b>> hClose :: Handle -> IO ()hClose errh :: Handleerrh)
($) :: (a -> b) -> a -> b$ \(inh,outh,errh,pid) -> do
hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode outh :: Handleouth outputBinary :: BooloutputBinary
hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode errh :: Handleerrh False :: BoolFalse
err <- hGetContents :: Handle -> IO StringhGetContents errh :: Handleerrh
out <- hGetContents :: Handle -> IO StringhGetContents outh :: Handleouth
mv <- newEmptyMVar :: IO (MVar a)newEmptyMVar
let force str = (evaluate :: a -> IO aevaluate (length :: [a] -> Intlength str :: Stringstr) (>>) :: Monad m => forall a b. m a -> m b -> m b>> return :: Monad m => forall a. a -> m areturn ())
finally :: IO a -> IO b -> IO a`Exception.finally` putMVar :: MVar a -> a -> IO ()putMVar mv :: MVar ()mv ()
_ <- forkIO :: IO () -> IO ThreadIdforkIO ($) :: (a -> b) -> a -> b$ force :: [a] -> IO ()force out :: Stringout
_ <- forkIO :: IO () -> IO ThreadIdforkIO ($) :: (a -> b) -> a -> b$ force :: [a] -> IO ()force err :: IOErrorerr
case input :: Maybe (String, Bool)input of
Nothing -> return :: Monad m => forall a. a -> m areturn ()
Just (inputStr, inputBinary) -> do
hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode inh :: Handleinh inputBinary :: BoolinputBinary
hPutStr :: Handle -> String -> IO ()hPutStr inh :: Handleinh inputStr :: StringinputStr
hClose :: Handle -> IO ()hClose inh :: Handleinh
takeMVar :: MVar a -> IO atakeMVar mv :: MVar ()mv
takeMVar :: MVar a -> IO atakeMVar mv :: MVar ()mv
exitcode <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess pid :: ProcessHandlepid
unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$
debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
(++) :: [a] -> [a] -> [a]++ if null :: [a] -> Boolnull err :: IOErrorerr then "" else
" with error message:\n" (++) :: [a] -> [a] -> [a]++ err :: IOErrorerr
return :: Monad m => forall a. a -> m areturn (out :: Stringout, err :: IOErrorerr, exitcode :: ExitCodeexitcode)
#else
tmpDir <- getTemporaryDirectory
withTempFile tmpDir ".cmd.stdout" $ \outName outHandle ->
withTempFile tmpDir ".cmd.stdin" $ \inName inHandle -> do
hClose outHandle
case input of
Nothing -> return ()
Just (inputStr, inputBinary) -> do
hSetBinaryMode inHandle inputBinary
hPutStr inHandle inputStr
hClose inHandle
let quote name = "'" ++ name ++ "'"
cmd = unwords (map quote (path:args))
++ " <" ++ quote inName
++ " >" ++ quote outName
exitcode <- system cmd
unless (exitcode == ExitSuccess) $
debug verbosity $ path ++ " returned " ++ show exitcode
Exception.bracket (openFile outName ReadMode) hClose $ \hnd -> do
hSetBinaryMode hnd outputBinary
output <- hGetContents hnd
length output `seq` return (output, "", exitcode)
#endif
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
findProgramLocation verbosity prog = do
debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "searching for " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " in path."
res <- findExecutable :: String -> IO (Maybe FilePath)findExecutable prog :: IO aprog
case res :: Maybe FilePathres of
Nothing -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ("Cannot find " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " on the path")
Just path -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ("found " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " at "(++) :: [a] -> [a] -> [a]++ path :: FilePathpath)
return :: Monad m => forall a. a -> m areturn res :: Maybe FilePathres
findProgramVersion :: String
-> (String -> String)
-> Verbosity
-> FilePath
-> IO (Maybe Version)
findProgramVersion versionArg selectVersion verbosity path = do
str <- rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO StringrawSystemStdout verbosity :: Verbosityverbosity path :: FilePathpath [versionArg :: StringversionArg]
catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` (\_ -> return :: Monad m => forall a. a -> m areturn "")
catchExit :: IO a -> (ExitCode -> IO a) -> IO a`catchExit` (\_ -> return :: Monad m => forall a. a -> m areturn "")
let version :: Maybe Version
version = simpleParse :: Text a => String -> Maybe asimpleParse (selectVersion :: String -> StringselectVersion str :: Stringstr)
case version :: Maybe Versionversion of
Nothing -> warn :: Verbosity -> String -> IO ()warn verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "cannot determine version of " (++) :: [a] -> [a] -> [a]++ path :: FilePathpath
(++) :: [a] -> [a] -> [a]++ " :\n" (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow str :: Stringstr
Just v -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " is version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay v :: Versionv
return :: Monad m => forall a. a -> m areturn version :: Maybe Versionversion
xargs :: Int -> ([String] -> IO ())
-> [String] -> [String] -> IO ()
xargs maxSize rawSystemFun fixedArgs bigArgs =
let fixedArgSize = sum :: Num a => [a] -> asum (map :: (a -> b) -> [a] -> [b]map length :: [a] -> Intlength fixedArgs :: [String]fixedArgs) (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength fixedArgs :: [String]fixedArgs
chunkSize = maxSize :: IntmaxSize (-) :: Num a => a -> a -> a fixedArgSize :: IntfixedArgSize
in mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (rawSystemFun :: [String] -> IO ()rawSystemFun (.) :: (b -> c) -> (a -> b) -> a -> c. (fixedArgs :: [String]fixedArgs (++) :: [a] -> [a] -> [a]++)) (chunks :: Int -> [[a]] -> [[[a]]]chunks chunkSize :: IntchunkSize bigArgs :: [String]bigArgs)
where chunks len = unfoldr :: (b -> Maybe (a, b)) -> b -> [a]unfoldr ($) :: (a -> b) -> a -> b$ \s ->
if null :: [a] -> Boolnull s :: [[a]]s then Nothing :: Maybe aNothing
else Just :: a -> Maybe aJust (chunk :: [[a]] -> Int -> [[a]] -> ([[a]], [[a]])chunk [] :: [a][] len :: Intlen s :: [[a]]s)
chunk acc _ [] = (reverse :: [a] -> [a]reverse acc :: [[a]]acc,[] :: [a][])
chunk acc len (s:ss)
| len' :: Intlen' (<) :: Ord a => a -> a -> Bool< len :: Intlen = chunk :: [[a]] -> Int -> [[a]] -> ([[a]], [[a]])chunk (s :: [[a]]s(:) :: a -> [a] -> [a]:acc :: [[a]]acc) (len :: Intlen(-) :: Num a => a -> a -> alen' :: Intlen'(-) :: Num a => a -> a -> a1) ss :: [[a]]ss
| otherwise :: Boolotherwise = (reverse :: [a] -> [a]reverse acc :: [[a]]acc, s :: [[a]]s(:) :: a -> [a] -> [a]:ss :: [[a]]ss)
where len' = length :: [a] -> Intlength s :: [[a]]s
findFile :: [FilePath]
-> FilePath
-> IO FilePath
findFile searchPath fileName =
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile id :: a -> aid
[ path :: FilePathpath (</>) :: FilePath -> FilePath -> FilePath</> fileName :: FilePathfileName
| path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath]
(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= maybe :: b -> (a -> b) -> Maybe a -> bmaybe (die :: String -> IO adie ($) :: (a -> b) -> a -> b$ fileName :: FilePathfileName (++) :: [a] -> [a] -> [a]++ " doesn't exist") return :: Monad m => forall a. a -> m areturn
findFileWithExtension :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe FilePath)
findFileWithExtension extensions searchPath baseName =
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile id :: a -> aid
[ path :: FilePathpath (</>) :: FilePath -> FilePath -> FilePath</> baseName :: FilePathbaseName (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext
| path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath
, ext <- nub :: Eq a => [a] -> [a]nub extensions :: [String]extensions ]
findFileWithExtension' :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe (FilePath, FilePath))
findFileWithExtension' extensions searchPath baseName =
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile (uncurry :: (a -> b -> c) -> (a, b) -> cuncurry (</>) :: FilePath -> FilePath -> FilePath(</>))
[ (path :: FilePathpath, baseName :: FilePathbaseName (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext)
| path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath
, ext <- nub :: Eq a => [a] -> [a]nub extensions :: [String]extensions ]
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile file = findFirst :: [a] -> IO (Maybe a)findFirst
where findFirst [] = return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
findFirst (x:xs) = do exists <- doesFileExist :: FilePath -> IO BooldoesFileExist (file :: FilePathfile x :: ax)
if exists :: Boolexists
then return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust x :: ax)
else findFirst :: [a] -> IO (Maybe a)findFirst xs :: [a]xs
findModuleFiles :: [FilePath]
-> [String]
-> [ModuleName]
-> IO [(FilePath, FilePath)]
findModuleFiles searchPath extensions moduleNames =
mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM (findModuleFile ::
[FilePath] -> [String] -> ModuleName -> IO (FilePath, FilePath)findModuleFile searchPath :: [FilePath]searchPath extensions :: [String]extensions) moduleNames :: [ModuleName]moduleNames
findModuleFile :: [FilePath]
-> [String]
-> ModuleName
-> IO (FilePath, FilePath)
findModuleFile searchPath extensions moduleName =
maybe :: b -> (a -> b) -> Maybe a -> bmaybe notFound :: IO anotFound return :: Monad m => forall a. a -> m areturn
(=<<) :: Monad m => (a -> m b) -> m a -> m b=<< findFileWithExtension' ::
[String]
-> [FilePath]
-> FilePath
-> IO (Maybe (FilePath, FilePath))findFileWithExtension' extensions :: [String]extensions searchPath :: [FilePath]searchPath
(toFilePath :: ModuleName -> FilePathModuleName.toFilePath moduleName :: ModuleNamemoduleName)
where
notFound = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Error: Could not find module: " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay moduleName :: ModuleNamemoduleName
(++) :: [a] -> [a] -> [a]++ " with any suffix: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow extensions :: [String]extensions
(++) :: [a] -> [a] -> [a]++ " in the search path: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow searchPath :: [FilePath]searchPath
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive topdir = recurseDirectories :: [FilePath] -> IO [FilePath]recurseDirectories [""]
where
recurseDirectories :: [FilePath] -> IO [FilePath]
recurseDirectories [] = return :: Monad m => forall a. a -> m areturn [] :: [a][]
recurseDirectories (dir:dirs) = unsafeInterleaveIO :: IO a -> IO aunsafeInterleaveIO ($) :: (a -> b) -> a -> b$ do
(files, dirs') <- collect ::
[FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect [] :: [a][] [] :: [a][] (=<<) :: Monad m => (a -> m b) -> m a -> m b=<< getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents (topdir :: FilePathtopdir (</>) :: FilePath -> FilePath -> FilePath</> dir :: FilePathdir)
files' <- recurseDirectories :: [FilePath] -> IO [FilePath]recurseDirectories (dirs' :: [FilePath]dirs' (++) :: [a] -> [a] -> [a]++ dirs :: [FilePath]dirs)
return :: Monad m => forall a. a -> m areturn (files :: [FilePath]files (++) :: [a] -> [a] -> [a]++ files' :: [FilePath]files')
where
collect files dirs' [] = return :: Monad m => forall a. a -> m areturn (reverse :: [a] -> [a]reverse files :: [FilePath]files, reverse :: [a] -> [a]reverse dirs' :: [FilePath]dirs')
collect files dirs' (entry:entries) | ignore :: [Char] -> Boolignore entry :: [Char]entry
= collect ::
[FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect files :: [FilePath]files dirs' :: [FilePath]dirs' entries :: [[Char]]entries
collect files dirs' (entry:entries) = do
let dirEntry = dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> entry :: [Char]entry
isDirectory <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist (topdir :: FilePathtopdir (</>) :: FilePath -> FilePath -> FilePath</> dirEntry :: FilePathdirEntry)
if isDirectory :: BoolisDirectory
then collect ::
[FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect files :: [FilePath]files (dirEntry :: FilePathdirEntry(:) :: a -> [a] -> [a]:dirs' :: [FilePath]dirs') entries :: [[Char]]entries
else collect ::
[FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect (dirEntry :: FilePathdirEntry(:) :: a -> [a] -> [a]:files :: [FilePath]files) dirs' :: [FilePath]dirs' entries :: [[Char]]entries
ignore ['.'] = True :: BoolTrue
ignore ['.', '.'] = True :: BoolTrue
ignore _ = False :: BoolFalse
data FileGlob
= NoGlob FilePath
| FileGlob FilePath String
parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions :: FilePath -> (FilePath, String)splitExtensions filepath :: FilePathfilepath of
(filepath', ext) -> case splitFileName :: FilePath -> (String, String)splitFileName filepath' :: FilePathfilepath' of
(dir, "*") | '*' elem :: Eq a => a -> [a] -> Bool`elem` dir :: FilePathdir
(||) :: Bool -> Bool -> Bool|| '*' elem :: Eq a => a -> [a] -> Bool`elem` ext :: Stringext
(||) :: Bool -> Bool -> Bool|| null :: [a] -> Boolnull ext :: Stringext -> Nothing :: Maybe aNothing
| null :: [a] -> Boolnull dir :: FilePathdir -> Just :: a -> Maybe aJust (FileGlob :: FilePath -> String -> FileGlobFileGlob "." ext :: Stringext)
| otherwise :: Boolotherwise -> Just :: a -> Maybe aJust (FileGlob :: FilePath -> String -> FileGlobFileGlob dir :: FilePathdir ext :: Stringext)
_ | '*' elem :: Eq a => a -> [a] -> Bool`elem` filepath :: FilePathfilepath -> Nothing :: Maybe aNothing
| otherwise :: Boolotherwise -> Just :: a -> Maybe aJust (NoGlob :: FilePath -> FileGlobNoGlob filepath :: FilePathfilepath)
matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]matchDirFileGlob "."
matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob :: FilePath -> Maybe FileGlobparseFileGlob filepath :: FilePathfilepath of
Nothing -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "invalid file glob '" (++) :: [a] -> [a] -> [a]++ filepath :: FilePathfilepath
(++) :: [a] -> [a] -> [a]++ "'. Wildcards '*' are only allowed in place of the file"
(++) :: [a] -> [a] -> [a]++ " name, not in the directory name or file extension."
(++) :: [a] -> [a] -> [a]++ " If a wildcard is used it must be with an file extension."
Just (NoGlob filepath') -> return :: Monad m => forall a. a -> m areturn [filepath' :: FilePathfilepath']
Just (FileGlob dir' ext) -> do
files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents (dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> dir' :: FilePathdir')
case [ dir' :: FilePathdir' (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
| file <- files :: [FilePath]files
, let (name, ext') = splitExtensions :: FilePath -> (FilePath, String)splitExtensions file :: FilePathfile
, not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext' :: Stringext' (==) :: Eq a => a -> a -> Bool== ext :: Stringext ] of
[] -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "filepath wildcard '" (++) :: [a] -> [a] -> [a]++ filepath :: FilePathfilepath
(++) :: [a] -> [a] -> [a]++ "' does not match any files."
matches -> return :: Monad m => forall a. a -> m areturn matches :: [FilePath]matches
createDirectoryIfMissingVerbose :: Verbosity
-> Bool
-> FilePath
-> IO ()
createDirectoryIfMissingVerbose verbosity create_parents path0
| create_parents :: Boolcreate_parents = createDirs :: [FilePath] -> IO ()createDirs (parents :: FilePath -> [FilePath]parents path0 :: FilePathpath0)
| otherwise :: Boolotherwise = createDirs :: [FilePath] -> IO ()createDirs (take :: Int -> [a] -> [a]take 1 (parents :: FilePath -> [FilePath]parents path0 :: FilePathpath0))
where
parents = reverse :: [a] -> [a]reverse (.) :: (b -> c) -> (a -> b) -> a -> c. scanl1 :: (a -> a -> a) -> [a] -> [a]scanl1 (</>) :: FilePath -> FilePath -> FilePath(</>) (.) :: (b -> c) -> (a -> b) -> a -> c. splitDirectories :: FilePath -> [FilePath]splitDirectories (.) :: (b -> c) -> (a -> b) -> a -> c. normalise :: FilePath -> FilePathnormalise
createDirs [] = return :: Monad m => forall a. a -> m areturn ()
createDirs (dir:[]) = createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir throwIOIO :: IOException -> IO athrowIOIO
createDirs (dir:dirs) =
createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir ($) :: (a -> b) -> a -> b$ \_ -> do
createDirs :: [FilePath] -> IO ()createDirs dirs :: [FilePath]dirs
createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir throwIOIO :: IOException -> IO athrowIOIO
createDir :: FilePath -> (IOException -> IO ()) -> IO ()
createDir dir notExistHandler = do
r <- tryIO :: IO a -> IO (Either IOException a)tryIO ($) :: (a -> b) -> a -> b$ createDirectoryVerbose :: Verbosity -> FilePath -> IO ()createDirectoryVerbose verbosity :: Verbosityverbosity dir :: FilePathdir
case (r :: Either IOException ()r :: Either IOException ()) of
Right () -> return :: Monad m => forall a. a -> m areturn ()
Left e
| isDoesNotExistError :: IOError -> BoolisDoesNotExistError e :: IOExceptione -> notExistHandler :: IOException -> IO ()notExistHandler e :: IOExceptione
| isAlreadyExistsError :: IOError -> BoolisAlreadyExistsError e :: IOExceptione -> (do
isDir <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist dir :: FilePathdir
if isDir :: BoolisDir then return :: Monad m => forall a. a -> m areturn ()
else throwIOIO :: IOException -> IO athrowIOIO e :: IOExceptione
) catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` ((\_ -> return :: Monad m => forall a. a -> m areturn ()) :: IOException -> IO ())
| otherwise :: Boolotherwise -> throwIOIO :: IOException -> IO athrowIOIO e :: IOExceptione
createDirectoryVerbose :: Verbosity -> FilePath -> IO ()
createDirectoryVerbose verbosity dir = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "creating " (++) :: [a] -> [a] -> [a]++ dir :: FilePathdir
createDirectory :: FilePath -> IO ()createDirectory dir :: FilePathdir
setDirOrdinary :: FilePath -> IO ()setDirOrdinary dir :: FilePathdir
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose verbosity src dest = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
copyFile :: FilePath -> FilePath -> IO ()copyFile src :: FilePathsrc dest :: FilePathdest
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile verbosity src dest = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("Installing " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
copyOrdinaryFile :: FilePath -> FilePath -> IO ()copyOrdinaryFile src :: FilePathsrc dest :: FilePathdest
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile verbosity src dest = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("Installing executable " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
copyExecutableFile :: FilePath -> FilePath -> IO ()copyExecutableFile src :: FilePathsrc dest :: FilePathdest
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles verbosity targetDir srcFiles = do
let dirs = map :: (a -> b) -> [a] -> [b]map (targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</>) (.) :: (b -> c) -> (a -> b) -> a -> c. nub :: Eq a => [a] -> [a]nub (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (takeDirectory :: FilePath -> FilePathtakeDirectory (.) :: (b -> c) -> (a -> b) -> a -> c. snd :: (a, b) -> bsnd) ($) :: (a -> b) -> a -> b$ srcFiles :: [FilePath]srcFiles
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue) dirs :: [FilePath]dirs
sequence_ :: Monad m => [m a] -> m ()sequence_ [ let src = srcBase :: FilePathsrcBase (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
dest = targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
in copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()copyFileVerbose verbosity :: Verbosityverbosity src :: FilePathsrc dest :: FilePathdest
| (srcBase, srcFile) <- srcFiles :: [FilePath]srcFiles ]
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles verbosity targetDir srcFiles = do
let dirs = map :: (a -> b) -> [a] -> [b]map (targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</>) (.) :: (b -> c) -> (a -> b) -> a -> c. nub :: Eq a => [a] -> [a]nub (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (takeDirectory :: FilePath -> FilePathtakeDirectory (.) :: (b -> c) -> (a -> b) -> a -> c. snd :: (a, b) -> bsnd) ($) :: (a -> b) -> a -> b$ srcFiles :: [FilePath]srcFiles
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue) dirs :: [FilePath]dirs
sequence_ :: Monad m => [m a] -> m ()sequence_ [ let src = srcBase :: FilePathsrcBase (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
dest = targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
in installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()installOrdinaryFile verbosity :: Verbosityverbosity src :: FilePathsrc dest :: FilePathdest
| (srcBase, srcFile) <- srcFiles :: [FilePath]srcFiles ]
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents verbosity srcDir destDir = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy directory '" (++) :: [a] -> [a] -> [a]++ srcDir :: FilePathsrcDir (++) :: [a] -> [a] -> [a]++ "' to '" (++) :: [a] -> [a] -> [a]++ destDir :: FilePathdestDir (++) :: [a] -> [a] -> [a]++ "'.")
srcFiles <- getDirectoryContentsRecursive :: FilePath -> IO [FilePath]getDirectoryContentsRecursive srcDir :: FilePathsrcDir
installOrdinaryFiles ::
Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()installOrdinaryFiles verbosity :: Verbosityverbosity destDir :: FilePathdestDir [ (srcDir :: FilePathsrcDir, f :: FilePathf) | f <- srcFiles :: [FilePath]srcFiles ]
smartCopySources :: Verbosity -> [FilePath] -> FilePath
-> [ModuleName] -> [String] -> IO ()
smartCopySources verbosity searchPath targetDir moduleNames extensions =
findModuleFiles ::
[FilePath] -> [String] -> [ModuleName] -> IO [(FilePath, FilePath)]findModuleFiles searchPath :: [FilePath]searchPath extensions :: [String]extensions moduleNames :: [ModuleName]moduleNames
(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= copyFiles ::
Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()copyFiles verbosity :: Verbosityverbosity targetDir :: FilePathtargetDir
copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursiveVerbose verbosity srcDir destDir = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy directory '" (++) :: [a] -> [a] -> [a]++ srcDir :: FilePathsrcDir (++) :: [a] -> [a] -> [a]++ "' to '" (++) :: [a] -> [a] -> [a]++ destDir :: FilePathdestDir (++) :: [a] -> [a] -> [a]++ "'.")
srcFiles <- getDirectoryContentsRecursive :: FilePath -> IO [FilePath]getDirectoryContentsRecursive srcDir :: FilePathsrcDir
copyFiles ::
Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()copyFiles verbosity :: Verbosityverbosity destDir :: FilePathdestDir [ (srcDir :: FilePathsrcDir, f :: FilePathf) | f <- srcFiles :: [FilePath]srcFiles ]
withTempFile :: FilePath
-> String
-> (FilePath -> Handle -> IO a) -> IO a
withTempFile tmpDir template action =
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
(openTempFile :: FilePath -> String -> IO (FilePath, Handle)openTempFile tmpDir :: FilePathtmpDir template :: Stringtemplate)
(\(name, handle) -> hClose :: Handle -> IO ()hClose handle :: IOError -> IO bhandle (>>) :: Monad m => forall a b. m a -> m b -> m b>> removeFile :: FilePath -> IO ()removeFile name :: Stringname)
(uncurry :: (a -> b -> c) -> (a, b) -> cuncurry action :: IO ()action)
withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a
withTempDirectory _verbosity targetDir template =
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
(createTempDirectory :: FilePath -> String -> IO FilePathcreateTempDirectory targetDir :: FilePathtargetDir template :: Stringtemplate)
removeDirectoryRecursive :: FilePath -> IO ()(removeDirectoryRecursive :: FilePath -> IO ()removeDirectoryRecursive)
withFileContents :: FilePath -> (String -> IO a) -> IO a
withFileContents name action =
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket (openFile :: FilePath -> IOMode -> IO HandleopenFile name :: Stringname ReadMode :: IOModeReadMode) hClose :: Handle -> IO ()hClose
(\hnd -> hGetContents :: Handle -> IO StringhGetContents hnd :: Handlehnd (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= action :: IO ()action)
writeFileAtomic :: FilePath -> String -> IO ()
writeFileAtomic targetFile content = do
(tmpFile, tmpHandle) <- openNewBinaryFile :: FilePath -> String -> IO (FilePath, Handle)openNewBinaryFile targetDir :: FilePathtargetDir template :: Stringtemplate
do hPutStr :: Handle -> String -> IO ()hPutStr tmpHandle :: HandletmpHandle content :: Stringcontent
hClose :: Handle -> IO ()hClose tmpHandle :: HandletmpHandle
renameFile :: FilePath -> FilePath -> IO ()renameFile tmpFile :: FilePathtmpFile targetFile :: FilePathtargetFile
onException :: IO a -> IO b -> IO a`onException` do hClose :: Handle -> IO ()hClose tmpHandle :: HandletmpHandle
removeFile :: FilePath -> IO ()removeFile tmpFile :: FilePathtmpFile
where
template = targetName :: StringtargetName (<.>) :: FilePath -> String -> FilePath<.> "tmp"
targetDir | null :: [a] -> Boolnull targetDir_ :: StringtargetDir_ = currentDir :: FilePathcurrentDir
| otherwise :: Boolotherwise = targetDir_ :: StringtargetDir_
(targetDir_,targetName) = splitFileName :: FilePath -> (String, String)splitFileName targetFile :: FilePathtargetFile
rewriteFile :: FilePath -> String -> IO ()
rewriteFile path newContent =
flip :: (a -> b -> c) -> b -> a -> cflip catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO mightNotExist :: IOError -> IO ()mightNotExist ($) :: (a -> b) -> a -> b$ do
existingContent <- readFile :: FilePath -> IO StringreadFile path :: FilePathpath
_ <- evaluate :: a -> IO aevaluate (length :: [a] -> Intlength existingContent :: StringexistingContent)
unless :: Monad m => Bool -> m () -> m ()unless (existingContent :: StringexistingContent (==) :: Eq a => a -> a -> Bool== newContent :: StringnewContent) ($) :: (a -> b) -> a -> b$
writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath newContent :: StringnewContent
where
mightNotExist e | isDoesNotExistError :: IOError -> BoolisDoesNotExistError e :: IOExceptione = writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath newContent :: StringnewContent
| otherwise :: Boolotherwise = ioError :: IOError -> IO aioError e :: IOExceptione
currentDir :: FilePath
currentDir = "."
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc _verbosity = findPackageDesc :: FilePath -> IO FilePathfindPackageDesc currentDir :: FilePathcurrentDir
findPackageDesc :: FilePath
-> IO FilePath
findPackageDesc dir
= do files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents dir :: FilePathdir
cabalFiles <- filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM doesFileExist :: FilePath -> IO BooldoesFileExist
[ dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
| file <- files :: [FilePath]files
, let (name, ext) = splitExtension :: FilePath -> (String, String)splitExtension file :: FilePathfile
, not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext :: Stringext (==) :: Eq a => a -> a -> Bool== ".cabal" ]
case cabalFiles :: [FilePath]cabalFiles of
[] -> noDesc :: IO anoDesc
[cabalFile] -> return :: Monad m => forall a. a -> m areturn cabalFile :: FilePathcabalFile
multiple -> multiDesc :: [String] -> IO amultiDesc multiple :: [FilePath]multiple
where
noDesc :: IO a
noDesc = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "No cabal file found.\n"
(++) :: [a] -> [a] -> [a]++ "Please create a package description file <pkgname>.cabal"
multiDesc :: [String] -> IO a
multiDesc l = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Multiple cabal files found.\n"
(++) :: [a] -> [a] -> [a]++ "Please use only one of: "
(++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow l :: [String]l
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = findHookedPackageDesc :: FilePath -> IO (Maybe FilePath)findHookedPackageDesc currentDir :: FilePathcurrentDir
findHookedPackageDesc
:: FilePath
-> IO (Maybe FilePath)
findHookedPackageDesc dir = do
files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents dir :: FilePathdir
buildInfoFiles <- filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM doesFileExist :: FilePath -> IO BooldoesFileExist
[ dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
| file <- files :: [FilePath]files
, let (name, ext) = splitExtension :: FilePath -> (String, String)splitExtension file :: FilePathfile
, not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext :: Stringext (==) :: Eq a => a -> a -> Bool== buildInfoExt :: StringbuildInfoExt ]
case buildInfoFiles :: [FilePath]buildInfoFiles of
[] -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
[f] -> return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust f :: FilePathf)
_ -> die :: String -> IO adie ("Multiple files with extension " (++) :: [a] -> [a] -> [a]++ buildInfoExt :: StringbuildInfoExt)
buildInfoExt :: String
buildInfoExt = ".buildinfo"
fromUTF8 :: String -> String
fromUTF8 [] = [] :: [a][]
fromUTF8 (c:cs)
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x7F' = c :: Charc (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xBF' = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xDF' = twoBytes :: Char -> [Char] -> [Char]twoBytes c :: Charc cs :: [Char]cs
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xEF' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 3 0x800 cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0xF)
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xF7' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 4 0x10000 cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x7)
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFB' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 5 0x200000 cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x3)
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFD' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 6 0x4000000 cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x1)
| otherwise :: Boolotherwise = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
where
twoBytes c0 (c1:cs')
| ord :: Char -> Intord c1 :: Charc1 (.&.) :: Bits a => a -> a -> a.&. 0xC0 (==) :: Eq a => a -> a -> Bool== 0x80
= let d = ((ord :: Char -> Intord c0 :: Charc0 (.&.) :: Bits a => a -> a -> a.&. 0x1F) shiftL :: Bits a => a -> Int -> a`shiftL` 6)
(.|.) :: Bits a => a -> a -> a.|. (ord :: Char -> Intord c1 :: Charc1 (.&.) :: Bits a => a -> a -> a.&. 0x3F)
in if d :: Intd (>=) :: Ord a => a -> a -> Bool>= 0x80
then chr :: Int -> Charchr d :: Intd (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
else replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
twoBytes _ cs' = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
moreBytes :: Int -> Int -> [Char] -> Int -> [Char]
moreBytes 1 overlong cs' acc
| overlong :: Intoverlong (<=) :: Ord a => a -> a -> Bool<= acc :: [[a]]acc (&&) :: Bool -> Bool -> Bool&& acc :: [[a]]acc (<=) :: Ord a => a -> a -> Bool<= 0x10FFFF
(&&) :: Bool -> Bool -> Bool&& (acc :: [[a]]acc (<) :: Ord a => a -> a -> Bool< 0xD800 (||) :: Bool -> Bool -> Bool|| 0xDFFF (<) :: Ord a => a -> a -> Bool< acc :: [[a]]acc)
(&&) :: Bool -> Bool -> Bool&& (acc :: [[a]]acc (<) :: Ord a => a -> a -> Bool< 0xFFFE (||) :: Bool -> Bool -> Bool|| 0xFFFF (<) :: Ord a => a -> a -> Bool< acc :: [[a]]acc)
= chr :: Int -> Charchr acc :: [[a]]acc (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
| otherwise :: Boolotherwise
= replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
moreBytes byteCount overlong (cn:cs') acc
| ord :: Char -> Intord cn :: Charcn (.&.) :: Bits a => a -> a -> a.&. 0xC0 (==) :: Eq a => a -> a -> Bool== 0x80
= moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes (byteCount :: IntbyteCount(-) :: Num a => a -> a -> a1) overlong :: Intoverlong cs' :: [Char]cs'
((acc :: [[a]]acc shiftL :: Bits a => a -> Int -> a`shiftL` 6) (.|.) :: Bits a => a -> a -> a.|. ord :: Char -> Intord cn :: Charcn (.&.) :: Bits a => a -> a -> a.&. 0x3F)
moreBytes _ _ cs' _
= replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
replacementChar = '\xfffd'
toUTF8 :: String -> String
toUTF8 [] = [] :: [a][]
toUTF8 (c:cs)
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x07F' = c :: Charc
(:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x7FF' = chr :: Int -> Charchr (0xC0 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
| c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFFFF'= chr :: Int -> Charchr (0xE0 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 12))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6) (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
| otherwise :: Boolotherwise = chr :: Int -> Charchr (0xf0 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 18))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 12) (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6) (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
(:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
where w = ord :: Char -> Intord c :: Charc
ignoreBOM :: String -> String
ignoreBOM ('\xFEFF':string) = string :: Stringstring
ignoreBOM string = string :: Stringstring
readUTF8File :: FilePath -> IO String
readUTF8File f = fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap (ignoreBOM :: String -> StringignoreBOM (.) :: (b -> c) -> (a -> b) -> a -> c. fromUTF8 :: String -> StringfromUTF8)
(.) :: (b -> c) -> (a -> b) -> a -> c. hGetContents :: Handle -> IO StringhGetContents (=<<) :: Monad m => (a -> m b) -> m a -> m b=<< openBinaryFile :: FilePath -> IOMode -> IO HandleopenBinaryFile f :: FilePathf ReadMode :: IOModeReadMode
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
withUTF8FileContents name action =
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
(openBinaryFile :: FilePath -> IOMode -> IO HandleopenBinaryFile name :: Stringname ReadMode :: IOModeReadMode)
hClose :: Handle -> IO ()hClose
(\hnd -> hGetContents :: Handle -> IO StringhGetContents hnd :: Handlehnd (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= action :: IO ()action (.) :: (b -> c) -> (a -> b) -> a -> c. ignoreBOM :: String -> StringignoreBOM (.) :: (b -> c) -> (a -> b) -> a -> c. fromUTF8 :: String -> StringfromUTF8)
writeUTF8File :: FilePath -> String -> IO ()
writeUTF8File path = writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath (.) :: (b -> c) -> (a -> b) -> a -> c. toUTF8 :: String -> StringtoUTF8
normaliseLineEndings :: String -> String
normaliseLineEndings [] = [] :: [a][]
normaliseLineEndings ('\r':'\n':s) = '\n' (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s
normaliseLineEndings ('\r':s) = '\n' (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s
normaliseLineEndings ( c :s) = c :: Charc (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s
equating :: Eq a => (b -> a) -> b -> b -> Bool
equating p x y = p :: b -> ap x :: ax (==) :: Eq a => a -> a -> Bool== p :: b -> ap y :: by
comparing :: Ord a => (b -> a) -> b -> b -> Ordering
comparing p x y = p :: b -> ap x :: ax compare :: Ord a => a -> a -> Ordering`compare` p :: b -> ap y :: by
isInfixOf :: String -> String -> Bool
isInfixOf needle haystack = any :: (a -> Bool) -> [a] -> Boolany (isPrefixOf :: Eq a => [a] -> [a] -> BoolisPrefixOf needle :: Stringneedle) (tails :: [a] -> [[a]]tails haystack :: Stringhaystack)
intercalate :: [a] -> [[a]] -> [a]
intercalate sep = concat :: [[a]] -> [a]concat (.) :: (b -> c) -> (a -> b) -> a -> c. intersperse :: a -> [a] -> [a]intersperse sep :: [a]sep
lowercase :: String -> String
lowercase = map :: (a -> b) -> [a] -> [b]map toLower :: Char -> CharChar.toLower