{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
#ifdef GIT_REV
{-# LANGUAGE TemplateHaskell #-}
#endif
module Distribution.Simple.Utils
( cabalVersion
, cabalGitInfo
, dieNoVerbosity
, die'
, dieWithException
, dieWithLocation'
, dieNoWrap
, topHandler
, topHandlerWith
, warn
, warnError
, notice
, noticeNoWrap
, noticeDoc
, setupMessage
, info
, infoNoWrap
, debug
, debugNoWrap
, chattyTry
, annotateIO
, exceptionWithMetadata
, withOutputMarker
, handleDoesNotExist
, ignoreSigPipe
, rawSystemExit
, rawSystemExitCode
, rawSystemProc
, rawSystemProcAction
, rawSystemExitWithEnv
, rawSystemExitWithEnvCwd
, rawSystemStdout
, rawSystemStdInOut
, rawSystemIOWithEnv
, rawSystemIOWithEnvAndAction
, fromCreatePipe
, maybeExit
, xargs
, findProgramVersion
, IOData (..)
, KnownIODataMode (..)
, IODataMode (..)
, VerboseException (..)
, createDirectoryIfMissingVerbose
, copyFileVerbose
, copyFiles
, copyFileTo
, copyFileToCwd
, installOrdinaryFile
, installExecutableFile
, installMaybeExecutableFile
, installOrdinaryFiles
, installExecutableFiles
, installMaybeExecutableFiles
, installDirectoryContents
, copyDirectoryRecursive
, doesExecutableExist
, setFileOrdinary
, setFileExecutable
, shortRelativePath
, dropExeExtension
, exeExtensions
, findFileEx
, findFileCwd
, findFirstFile
, Suffix (..)
, findFileWithExtension
, findFileCwdWithExtension
, findFileWithExtension'
, findFileCwdWithExtension'
, findAllFilesWithExtension
, findAllFilesCwdWithExtension
, findModuleFileEx
, findModuleFileCwd
, findModuleFilesEx
, findModuleFilesCwd
, getDirectoryContentsRecursive
, isInSearchPath
, addLibraryPath
, moreRecentFile
, existsAndIsMoreRecentThan
, TempFileOptions (..)
, defaultTempFileOptions
, withTempFile
, withTempFileCwd
, withTempFileEx
, withTempDirectory
, withTempDirectoryCwd
, withTempDirectoryEx
, withTempDirectoryCwdEx
, createTempDirectory
, defaultPackageDescCwd
, findPackageDesc
, tryFindPackageDesc
, findHookedPackageDesc
, withFileContents
, writeFileAtomic
, rewriteFileEx
, rewriteFileLBS
, fromUTF8BS
, fromUTF8LBS
, toUTF8BS
, toUTF8LBS
, readUTF8File
, withUTF8FileContents
, writeUTF8File
, normaliseLineEndings
, ignoreBOM
, dropWhileEndLE
, takeWhileEndLE
, equating
, comparing
, isInfixOf
, intercalate
, lowercase
, listUnion
, listUnionRight
, ordNub
, sortNub
, ordNubBy
, ordNubRight
, safeHead
, safeTail
, safeLast
, safeInit
, unintersperse
, wrapText
, wrapLine
, stripCommonPrefix
, isAbsoluteOnAnyPlatform
, isRelativeOnAnyPlatform
, exceptionWithCallStackPrefix
) where
import Distribution.Compat.Async (waitCatch, withAsyncNF)
import Distribution.Compat.CopyFile
import Distribution.Compat.FilePath as FilePath
import Distribution.Compat.Internal.TempFile
import Distribution.Compat.Lens (Lens', over)
import Distribution.Compat.Prelude
import Distribution.Compat.Stack
import Distribution.ModuleName as ModuleName
import Distribution.Simple.Errors
import Distribution.Simple.PreProcess.Types
import Distribution.System
import Distribution.Types.PackageId
import Distribution.Utils.Generic
import Distribution.Utils.IOData (IOData (..), IODataMode (..), KnownIODataMode (..))
import qualified Distribution.Utils.IOData as IOData
import Distribution.Utils.Path
import Distribution.Verbosity
import Distribution.Version
import Prelude ()
#ifdef CURRENT_PACKAGE_KEY
#define BOOTSTRAPPED_CABAL 1
#endif
#ifdef BOOTSTRAPPED_CABAL
import qualified Paths_Cabal (version)
#endif
import Distribution.Parsec
import Distribution.Pretty
import qualified Data.ByteString.Lazy as BS
import Data.Typeable
( cast
)
import qualified Control.Exception as Exception
import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime)
import Distribution.Compat.Process (proc)
import Foreign.C.Error (Errno (..), ePIPE)
import qualified GHC.IO.Exception as GHC
import GHC.Stack (HasCallStack)
import Numeric (showFFloat)
import System.Directory
( Permissions (executable)
, createDirectory
, doesDirectoryExist
, doesFileExist
, getDirectoryContents
, getModificationTime
, getPermissions
, getTemporaryDirectory
, removeDirectoryRecursive
, removeFile
)
import System.Environment
( getProgName
)
import System.FilePath (takeFileName)
import System.FilePath as FilePath
( getSearchPath
, joinPath
, normalise
, searchPathSeparator
, splitDirectories
, splitExtension
, takeDirectory
)
import System.IO
( BufferMode (..)
, Handle
, hClose
, hFlush
, hGetContents
, hPutStr
, hPutStrLn
, hSetBinaryMode
, hSetBuffering
, stderr
, stdout
)
import System.IO.Error
import System.IO.Unsafe
( unsafeInterleaveIO
)
import qualified System.Process as Process
import qualified Text.PrettyPrint as Disp
#ifdef GIT_REV
import Data.Either (isLeft)
import GitHash
( giHash
, giBranch
, giCommitDate
, tGitInfoCwdTry
)
#endif
cabalVersion :: Version
#if defined(BOOTSTRAPPED_CABAL)
cabalVersion :: Version
cabalVersion = Version -> Version
mkVersion' Version
Paths_Cabal.version
#elif defined(CABAL_VERSION)
cabalVersion = mkVersion [CABAL_VERSION]
#else
cabalVersion = mkVersion [3,0]
#endif
cabalGitInfo :: String
#ifdef GIT_REV
cabalGitInfo = if giHash' == ""
then ""
else concat [ "(commit "
, giHash'
, branchInfo
, ", "
, either (const "") giCommitDate gi'
, ")"
]
where
gi' = $$tGitInfoCwdTry
giHash' = take 7 . either (const "") giHash $ gi'
branchInfo | isLeft gi' = ""
| either id giBranch gi' == "master" = ""
| otherwise = " on " <> either id giBranch gi'
#else
cabalGitInfo :: [Char]
cabalGitInfo = [Char]
""
#endif
dieNoVerbosity :: String -> IO a
dieNoVerbosity :: forall a. [Char] -> IO a
dieNoVerbosity [Char]
msg =
IOException -> IO a
forall a. HasCallStack => IOException -> IO a
ioError ([Char] -> IOException
userError [Char]
msg)
where
CallStack
_ = CallStack
HasCallStack => CallStack
callStack
ioeSetVerbatim :: IOError -> IOError
ioeSetVerbatim :: IOException -> IOException
ioeSetVerbatim IOException
e = IOException -> [Char] -> IOException
ioeSetLocation IOException
e [Char]
"dieVerbatim"
ioeGetVerbatim :: IOError -> Bool
ioeGetVerbatim :: IOException -> Bool
ioeGetVerbatim IOException
e = IOException -> [Char]
ioeGetLocation IOException
e [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"dieVerbatim"
verbatimUserError :: String -> IOError
verbatimUserError :: [Char] -> IOException
verbatimUserError = IOException -> IOException
ioeSetVerbatim (IOException -> IOException)
-> ([Char] -> IOException) -> [Char] -> IOException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> IOException
userError
dieWithLocation' :: Verbosity -> FilePath -> Maybe Int -> String -> IO a
dieWithLocation' :: forall a. Verbosity -> [Char] -> Maybe Int -> [Char] -> IO a
dieWithLocation' Verbosity
verbosity [Char]
filename Maybe Int
mb_lineno [Char]
msg =
Verbosity -> [Char] -> IO a
forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity ([Char] -> IO a) -> [Char] -> IO a
forall a b. (a -> b) -> a -> b
$
[Char]
filename
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ( case Maybe Int
mb_lineno of
Just Int
lineno -> [Char]
":" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
lineno
Maybe Int
Nothing -> [Char]
""
)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
msg
die' :: Verbosity -> String -> IO a
die' :: forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity [Char]
msg = (HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ do
IOException -> IO a
forall a. HasCallStack => IOException -> IO a
ioError (IOException -> IO a) -> ([Char] -> IOException) -> [Char] -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> IOException
verbatimUserError
([Char] -> IO a) -> IO [Char] -> IO a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> [Char] -> IO [Char]
annotateErrorString Verbosity
verbosity
([Char] -> IO [Char]) -> IO [Char] -> IO [Char]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Char] -> IO [Char]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> IO [Char]) -> ([Char] -> [Char]) -> [Char] -> IO [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> [Char] -> [Char]
wrapTextVerbosity Verbosity
verbosity
([Char] -> IO [Char]) -> IO [Char] -> IO [Char]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Char] -> IO [Char]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> IO [Char]) -> ([Char] -> [Char]) -> [Char] -> IO [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
addErrorPrefix
([Char] -> IO [Char]) -> IO [Char] -> IO [Char]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Char] -> IO [Char]
prefixWithProgName [Char]
msg
data VerboseException a = VerboseException CallStack POSIXTime Verbosity a
deriving (Int -> VerboseException a -> [Char] -> [Char]
[VerboseException a] -> [Char] -> [Char]
VerboseException a -> [Char]
(Int -> VerboseException a -> [Char] -> [Char])
-> (VerboseException a -> [Char])
-> ([VerboseException a] -> [Char] -> [Char])
-> Show (VerboseException a)
forall a. Show a => Int -> VerboseException a -> [Char] -> [Char]
forall a. Show a => [VerboseException a] -> [Char] -> [Char]
forall a. Show a => VerboseException a -> [Char]
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: forall a. Show a => Int -> VerboseException a -> [Char] -> [Char]
showsPrec :: Int -> VerboseException a -> [Char] -> [Char]
$cshow :: forall a. Show a => VerboseException a -> [Char]
show :: VerboseException a -> [Char]
$cshowList :: forall a. Show a => [VerboseException a] -> [Char] -> [Char]
showList :: [VerboseException a] -> [Char] -> [Char]
Show)
dieWithException :: (HasCallStack, Show a1, Typeable a1, Exception (VerboseException a1)) => Verbosity -> a1 -> IO a
dieWithException :: forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity a1
exception = do
ts <- IO NominalDiffTime
getPOSIXTime
throwIO $ VerboseException callStack ts verbosity exception
instance Exception (VerboseException CabalException) where
displayException :: VerboseException CabalException -> [Char]
displayException :: VerboseException CabalException -> [Char]
displayException (VerboseException CallStack
stack NominalDiffTime
timestamp Verbosity
verb CabalException
cabalexception) =
Verbosity -> [Char] -> [Char]
withOutputMarker
Verbosity
verb
( [[Char]] -> [Char]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [Char]
"Error: [Cabal-"
, Int -> [Char]
forall a. Show a => a -> [Char]
show (CabalException -> Int
exceptionCode CabalException
cabalexception)
, [Char]
"]\n"
]
)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CallStack -> NominalDiffTime -> Verbosity -> [Char] -> [Char]
exceptionWithMetadata CallStack
stack NominalDiffTime
timestamp Verbosity
verb (CabalException -> [Char]
exceptionMessage CabalException
cabalexception)
dieNoWrap :: Verbosity -> String -> IO a
dieNoWrap :: forall a. Verbosity -> [Char] -> IO a
dieNoWrap Verbosity
verbosity [Char]
msg = (HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ do
IOException -> IO a
forall a. HasCallStack => IOException -> IO a
ioError (IOException -> IO a) -> ([Char] -> IOException) -> [Char] -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> IOException
verbatimUserError
([Char] -> IO a) -> IO [Char] -> IO a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> [Char] -> IO [Char]
annotateErrorString
Verbosity
verbosity
([Char] -> [Char]
addErrorPrefix [Char]
msg)
addErrorPrefix :: String -> String
addErrorPrefix :: [Char] -> [Char]
addErrorPrefix [Char]
msg
| [Char]
errorPrefix [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [Char]
msg = [Char]
msg
| Bool
otherwise = [[Char]] -> [Char]
unwords [[Char]
errorPrefix, [Char]
msg]
errorPrefix :: String
errorPrefix :: [Char]
errorPrefix = [Char]
"Error:"
prefixWithProgName :: String -> IO String
prefixWithProgName :: [Char] -> IO [Char]
prefixWithProgName [Char]
msg = do
pname <- IO [Char]
getProgName
return $ pname ++ ": " ++ msg
annotateErrorString :: Verbosity -> String -> IO String
annotateErrorString :: Verbosity -> [Char] -> IO [Char]
annotateErrorString Verbosity
verbosity [Char]
msg = do
ts <- IO NominalDiffTime
getPOSIXTime
return $ withMetadata ts AlwaysMark VerboseTrace verbosity msg
annotateIO :: Verbosity -> IO a -> IO a
annotateIO :: forall a. Verbosity -> IO a -> IO a
annotateIO Verbosity
verbosity IO a
act = do
ts <- IO NominalDiffTime
getPOSIXTime
flip modifyIOError act $
ioeModifyErrorString $
withMetadata ts NeverMark VerboseTrace verbosity
ioeModifyErrorString :: (String -> String) -> IOError -> IOError
ioeModifyErrorString :: ([Char] -> [Char]) -> IOException -> IOException
ioeModifyErrorString = ASetter IOException IOException [Char] [Char]
-> ([Char] -> [Char]) -> IOException -> IOException
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter IOException IOException [Char] [Char]
Lens' IOException [Char]
ioeErrorString
ioeErrorString :: Lens' IOError String
ioeErrorString :: Lens' IOException [Char]
ioeErrorString [Char] -> f [Char]
f IOException
ioe = IOException -> [Char] -> IOException
ioeSetErrorString IOException
ioe ([Char] -> IOException) -> f [Char] -> f IOException
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> f [Char]
f (IOException -> [Char]
ioeGetErrorString IOException
ioe)
{-# NOINLINE topHandlerWith #-}
topHandlerWith :: forall a. (Exception.SomeException -> IO a) -> IO a -> IO a
topHandlerWith :: forall a. (SomeException -> IO a) -> IO a -> IO a
topHandlerWith SomeException -> IO a
cont IO a
prog = do
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stderr BufferMode
LineBuffering
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
Exception.catches
IO a
prog
[ (AsyncException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Exception.Handler AsyncException -> IO a
rethrowAsyncExceptions
, (ExitCode -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Exception.Handler ExitCode -> IO a
rethrowExitStatus
, (SomeException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Exception.Handler SomeException -> IO a
handle
]
where
rethrowAsyncExceptions :: Exception.AsyncException -> IO a
rethrowAsyncExceptions :: AsyncException -> IO a
rethrowAsyncExceptions AsyncException
a = AsyncException -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO AsyncException
a
rethrowExitStatus :: ExitCode -> IO a
rethrowExitStatus :: ExitCode -> IO a
rethrowExitStatus = ExitCode -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO
handle :: Exception.SomeException -> IO a
handle :: SomeException -> IO a
handle SomeException
se = do
Handle -> IO ()
hFlush Handle
stdout
pname <- IO [Char]
getProgName
hPutStr stderr (message pname se)
cont se
message :: String -> Exception.SomeException -> String
message :: [Char] -> SomeException -> [Char]
message [Char]
pname (Exception.SomeException e
se) =
case e -> Maybe IOException
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
se :: Maybe Exception.IOException of
Just IOException
ioe
| IOException -> Bool
ioeGetVerbatim IOException
ioe ->
IOException -> [Char]
ioeGetErrorString IOException
ioe [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n"
| IOException -> Bool
isUserError IOException
ioe ->
let file :: [Char]
file = case IOException -> Maybe [Char]
ioeGetFileName IOException
ioe of
Maybe [Char]
Nothing -> [Char]
""
Just [Char]
path -> [Char]
path [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
location [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": "
location :: [Char]
location = case IOException -> [Char]
ioeGetLocation IOException
ioe of
l :: [Char]
l@(Char
n : [Char]
_) | Char -> Bool
isDigit Char
n -> Char
':' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
l
[Char]
_ -> [Char]
""
detail :: [Char]
detail = IOException -> [Char]
ioeGetErrorString IOException
ioe
in [Char] -> [Char]
wrapText ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
addErrorPrefix ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
pname [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
file [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
detail
Maybe IOException
_ ->
e -> [Char]
forall e. Exception e => e -> [Char]
displaySomeException e
se [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n"
displaySomeException :: Exception.Exception e => e -> String
displaySomeException :: forall e. Exception e => e -> [Char]
displaySomeException e
se = e -> [Char]
forall e. Exception e => e -> [Char]
Exception.displayException e
se
topHandler :: IO a -> IO a
topHandler :: forall a. IO a -> IO a
topHandler IO a
prog = (SomeException -> IO a) -> IO a -> IO a
forall a. (SomeException -> IO a) -> IO a -> IO a
topHandlerWith (IO a -> SomeException -> IO a
forall a b. a -> b -> a
const (IO a -> SomeException -> IO a) -> IO a -> SomeException -> IO a
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)) IO a
prog
verbosityHandle :: Verbosity -> Handle
verbosityHandle :: Verbosity -> Handle
verbosityHandle Verbosity
verbosity
| Verbosity -> Bool
isVerboseStderr Verbosity
verbosity = Handle
stderr
| Bool
otherwise = Handle
stdout
warn :: Verbosity -> String -> IO ()
warn :: Verbosity -> [Char] -> IO ()
warn Verbosity
verbosity [Char]
msg = [Char] -> Verbosity -> [Char] -> IO ()
warnMessage [Char]
"Warning" Verbosity
verbosity [Char]
msg
warnError :: Verbosity -> String -> IO ()
warnError :: Verbosity -> [Char] -> IO ()
warnError Verbosity
verbosity [Char]
message = [Char] -> Verbosity -> [Char] -> IO ()
warnMessage [Char]
"Error" Verbosity
verbosity [Char]
message
warnMessage :: String -> Verbosity -> String -> IO ()
warnMessage :: [Char] -> Verbosity -> [Char] -> IO ()
warnMessage [Char]
l Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal) Bool -> Bool -> Bool
&& Bool -> Bool
not (Verbosity -> Bool
isVerboseNoWarn Verbosity
verbosity)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
ts <- IO NominalDiffTime
getPOSIXTime
hFlush stdout
hPutStr stderr
. withMetadata ts NormalMark FlagTrace verbosity
. wrapTextVerbosity verbosity
$ l ++ ": " ++ msg
notice :: Verbosity -> String -> IO ()
notice :: Verbosity -> [Char] -> IO ()
notice Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NormalMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
noticeNoWrap :: Verbosity -> String -> IO ()
noticeNoWrap :: Verbosity -> [Char] -> IO ()
noticeNoWrap Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h . withMetadata ts NormalMark FlagTrace verbosity $ msg
noticeDoc :: Verbosity -> Disp.Doc -> IO ()
noticeDoc :: Verbosity -> Doc -> IO ()
noticeDoc Verbosity
verbosity Doc
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NormalMark FlagTrace verbosity $
Disp.renderStyle defaultStyle $
msg
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage :: Verbosity -> [Char] -> PackageIdentifier -> IO ()
setupMessage Verbosity
verbosity [Char]
msg PackageIdentifier
pkgid = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
noticeNoWrap Verbosity
verbosity ([Char]
msg [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Char
' ' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: PackageIdentifier -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow PackageIdentifier
pkgid [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"...")
info :: Verbosity -> String -> IO ()
info :: Verbosity -> [Char] -> IO ()
info Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
infoNoWrap :: Verbosity -> String -> IO ()
infoNoWrap :: Verbosity -> [Char] -> IO ()
infoNoWrap Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
msg
debug :: Verbosity -> String -> IO ()
debug :: Verbosity -> [Char] -> IO ()
debug Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
deafening) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
hFlush stdout
debugNoWrap :: Verbosity -> String -> IO ()
debugNoWrap :: Verbosity -> [Char] -> IO ()
debugNoWrap Verbosity
verbosity [Char]
msg = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
deafening) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let h :: Handle
h = Verbosity -> Handle
verbosityHandle Verbosity
verbosity
ts <- IO NominalDiffTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
msg
hFlush stdout
chattyTry
:: String
-> IO ()
-> IO ()
chattyTry :: [Char] -> IO () -> IO ()
chattyTry [Char]
desc IO ()
action =
IO () -> (IOException -> IO ()) -> IO ()
forall a. IO a -> (IOException -> IO a) -> IO a
catchIO IO ()
action ((IOException -> IO ()) -> IO ())
-> (IOException -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IOException
exception ->
Handle -> [Char] -> IO ()
hPutStrLn Handle
stderr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"Error while " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
desc [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ IOException -> [Char]
forall a. Show a => a -> [Char]
show IOException
exception
handleDoesNotExist :: a -> IO a -> IO a
handleDoesNotExist :: forall a. a -> IO a -> IO a
handleDoesNotExist a
e =
(IOException -> Maybe IOException)
-> (IOException -> IO a) -> IO a -> IO a
forall e b a.
Exception e =>
(e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
Exception.handleJust
(\IOException
ioe -> if IOException -> Bool
isDoesNotExistError IOException
ioe then IOException -> Maybe IOException
forall a. a -> Maybe a
Just IOException
ioe else Maybe IOException
forall a. Maybe a
Nothing)
(\IOException
_ -> a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
e)
wrapTextVerbosity :: Verbosity -> String -> String
wrapTextVerbosity :: Verbosity -> [Char] -> [Char]
wrapTextVerbosity Verbosity
verb
| Verbosity -> Bool
isVerboseNoWrap Verbosity
verb = [Char] -> [Char]
withTrailingNewline
| Bool
otherwise = [Char] -> [Char]
withTrailingNewline ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
wrapText
withTimestamp :: Verbosity -> POSIXTime -> String -> String
withTimestamp :: Verbosity -> NominalDiffTime -> [Char] -> [Char]
withTimestamp Verbosity
v NominalDiffTime
ts [Char]
msg
| Verbosity -> Bool
isVerboseTimestamp Verbosity
v = [Char]
msg'
| Bool
otherwise = [Char]
msg
where
msg' :: [Char]
msg' = case [Char] -> [[Char]]
lines [Char]
msg of
[] -> [Char] -> [Char]
tsstr [Char]
"\n"
[Char]
l1 : [[Char]]
rest -> [[Char]] -> [Char]
unlines ([Char] -> [Char]
tsstr (Char
' ' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
l1) [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char]
contpfx [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++) [[Char]]
rest)
tsstr :: [Char] -> [Char]
tsstr = Maybe Int -> Double -> [Char] -> [Char]
forall a. RealFloat a => Maybe Int -> a -> [Char] -> [Char]
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
3) (NominalDiffTime -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac NominalDiffTime
ts :: Double)
contpfx :: [Char]
contpfx = Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate ([Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char] -> [Char]
tsstr [Char]
" ")) Char
' '
withOutputMarker :: Verbosity -> String -> String
withOutputMarker :: Verbosity -> [Char] -> [Char]
withOutputMarker Verbosity
v [Char]
xs | Bool -> Bool
not (Verbosity -> Bool
isVerboseMarkOutput Verbosity
v) = [Char]
xs
withOutputMarker Verbosity
_ [Char]
"" = [Char]
""
withOutputMarker Verbosity
_ [Char]
xs =
[Char]
"-----BEGIN CABAL OUTPUT-----\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
withTrailingNewline [Char]
xs
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-----END CABAL OUTPUT-----\n"
withTrailingNewline :: String -> String
withTrailingNewline :: [Char] -> [Char]
withTrailingNewline [Char]
"" = [Char]
""
withTrailingNewline (Char
x : [Char]
xs) = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char -> [Char] -> [Char]
go Char
x [Char]
xs
where
go :: Char -> [Char] -> [Char]
go Char
_ (Char
c : [Char]
cs) = Char
c Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char -> [Char] -> [Char]
go Char
c [Char]
cs
go Char
'\n' [Char]
"" = [Char]
""
go Char
_ [Char]
"" = [Char]
"\n"
withCallStackPrefix :: WithCallStack (TraceWhen -> Verbosity -> String -> String)
withCallStackPrefix :: WithCallStack (TraceWhen -> Verbosity -> [Char] -> [Char])
withCallStackPrefix TraceWhen
tracer Verbosity
verbosity [Char]
s =
(HasCallStack => [Char]) -> [Char]
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => [Char]) -> [Char])
-> (HasCallStack => [Char]) -> [Char]
forall a b. (a -> b) -> a -> b
$
( if Verbosity -> Bool
isVerboseCallSite Verbosity
verbosity
then
[Char]
HasCallStack => [Char]
parentSrcLocPrefix
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
if Verbosity -> Bool
isVerboseMarkOutput Verbosity
verbosity
then [Char]
"\n"
else [Char]
""
else [Char]
""
)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ( case Verbosity -> TraceWhen -> Maybe [Char]
traceWhen Verbosity
verbosity TraceWhen
tracer of
Just [Char]
pre -> [Char]
pre [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CallStack -> [Char]
prettyCallStack CallStack
HasCallStack => CallStack
callStack [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n"
Maybe [Char]
Nothing -> [Char]
""
)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
s
data TraceWhen
= AlwaysTrace
| VerboseTrace
| FlagTrace
deriving (TraceWhen -> TraceWhen -> Bool
(TraceWhen -> TraceWhen -> Bool)
-> (TraceWhen -> TraceWhen -> Bool) -> Eq TraceWhen
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceWhen -> TraceWhen -> Bool
== :: TraceWhen -> TraceWhen -> Bool
$c/= :: TraceWhen -> TraceWhen -> Bool
/= :: TraceWhen -> TraceWhen -> Bool
Eq)
traceWhen :: Verbosity -> TraceWhen -> Maybe String
traceWhen :: Verbosity -> TraceWhen -> Maybe [Char]
traceWhen Verbosity
_ TraceWhen
AlwaysTrace = [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
""
traceWhen Verbosity
v TraceWhen
VerboseTrace | Verbosity
v Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose = [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
""
traceWhen Verbosity
v TraceWhen
FlagTrace | Verbosity -> Bool
isVerboseCallStack Verbosity
v = [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
"----\n"
traceWhen Verbosity
_ TraceWhen
_ = Maybe [Char]
forall a. Maybe a
Nothing
data MarkWhen = AlwaysMark | NormalMark | NeverMark
withMetadata :: WithCallStack (POSIXTime -> MarkWhen -> TraceWhen -> Verbosity -> String -> String)
withMetadata :: WithCallStack
(NominalDiffTime
-> MarkWhen -> TraceWhen -> Verbosity -> [Char] -> [Char])
withMetadata NominalDiffTime
ts MarkWhen
marker TraceWhen
tracer Verbosity
verbosity [Char]
x =
(HasCallStack => [Char]) -> [Char]
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
((HasCallStack => [Char]) -> [Char])
-> (HasCallStack => [Char]) -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char] -> [Char]
withTrailingNewline
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithCallStack (TraceWhen -> Verbosity -> [Char] -> [Char])
TraceWhen -> Verbosity -> [Char] -> [Char]
withCallStackPrefix TraceWhen
tracer Verbosity
verbosity
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ( case MarkWhen
marker of
MarkWhen
AlwaysMark -> Verbosity -> [Char] -> [Char]
withOutputMarker Verbosity
verbosity
MarkWhen
NormalMark
| Bool -> Bool
not (Verbosity -> Bool
isVerboseQuiet Verbosity
verbosity) ->
Verbosity -> [Char] -> [Char]
withOutputMarker Verbosity
verbosity
| Bool
otherwise ->
[Char] -> [Char]
forall a. a -> a
id
MarkWhen
NeverMark -> [Char] -> [Char]
forall a. a -> a
id
)
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
clearMarkers
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> NominalDiffTime -> [Char] -> [Char]
withTimestamp Verbosity
verbosity NominalDiffTime
ts
([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
x
exceptionWithMetadata :: CallStack -> POSIXTime -> Verbosity -> String -> String
exceptionWithMetadata :: CallStack -> NominalDiffTime -> Verbosity -> [Char] -> [Char]
exceptionWithMetadata CallStack
stack NominalDiffTime
ts Verbosity
verbosity [Char]
x =
[Char] -> [Char]
withTrailingNewline
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallStack -> Verbosity -> [Char] -> [Char]
exceptionWithCallStackPrefix CallStack
stack Verbosity
verbosity
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> [Char] -> [Char]
withOutputMarker Verbosity
verbosity
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
clearMarkers
([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> NominalDiffTime -> [Char] -> [Char]
withTimestamp Verbosity
verbosity NominalDiffTime
ts
([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
x
clearMarkers :: String -> String
clearMarkers :: [Char] -> [Char]
clearMarkers [Char]
s = [[Char]] -> [Char]
unlines ([[Char]] -> [Char])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Char] -> Bool
isMarker ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]]
lines [Char]
s
where
isMarker :: [Char] -> Bool
isMarker [Char]
"-----BEGIN CABAL OUTPUT-----" = Bool
False
isMarker [Char]
"-----END CABAL OUTPUT-----" = Bool
False
isMarker [Char]
_ = Bool
True
exceptionWithCallStackPrefix :: CallStack -> Verbosity -> String -> String
exceptionWithCallStackPrefix :: CallStack -> Verbosity -> [Char] -> [Char]
exceptionWithCallStackPrefix CallStack
stack Verbosity
verbosity [Char]
s =
[Char]
s
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (HasCallStack => [Char]) -> [Char]
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
( ( if Verbosity -> Bool
isVerboseCallSite Verbosity
verbosity
then
[Char]
HasCallStack => [Char]
parentSrcLocPrefix
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
if Verbosity -> Bool
isVerboseMarkOutput Verbosity
verbosity
then [Char]
"\n"
else [Char]
""
else [Char]
""
)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ( if Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose
then CallStack -> [Char]
prettyCallStack CallStack
stack [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n"
else [Char]
""
)
)
maybeExit :: IO ExitCode -> IO ()
maybeExit :: IO ExitCode -> IO ()
maybeExit IO ExitCode
cmd = do
exitcode <- IO ExitCode
cmd
unless (exitcode == ExitSuccess) $ exitWith exitcode
logCommand :: Verbosity -> Process.CreateProcess -> IO ()
logCommand :: Verbosity -> CreateProcess -> IO ()
logCommand Verbosity
verbosity CreateProcess
cp = do
Verbosity -> [Char] -> IO ()
infoNoWrap Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char]
"Running: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> case CreateProcess -> CmdSpec
Process.cmdspec CreateProcess
cp of
Process.ShellCommand [Char]
sh -> [Char]
sh
Process.RawCommand [Char]
path [[Char]]
args -> [Char] -> [[Char]] -> [Char]
Process.showCommandForUser [Char]
path [[Char]]
args
case CreateProcess -> Maybe [([Char], [Char])]
Process.env CreateProcess
cp of
Just [([Char], [Char])]
env -> Verbosity -> [Char] -> IO ()
debugNoWrap Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"with environment: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [([Char], [Char])] -> [Char]
forall a. Show a => a -> [Char]
show [([Char], [Char])]
env
Maybe [([Char], [Char])]
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
case CreateProcess -> Maybe [Char]
Process.cwd CreateProcess
cp of
Just [Char]
cwd -> Verbosity -> [Char] -> IO ()
debugNoWrap Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"with working directory: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
cwd
Maybe [Char]
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Handle -> IO ()
hFlush Handle
stdout
rawSystemExit :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> FilePath -> [String] -> IO ()
rawSystemExit :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Char]
-> [[Char]]
-> IO ()
rawSystemExit Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Char]
path [[Char]]
args =
(HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
IO ExitCode -> IO ()
maybeExit (IO ExitCode -> IO ()) -> IO ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Char]
-> [[Char]]
-> Maybe [([Char], [Char])]
-> IO ExitCode
rawSystemExitCode Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Char]
path [[Char]]
args Maybe [([Char], [Char])]
forall a. Maybe a
Nothing
rawSystemExitCode
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> FilePath
-> [String]
-> Maybe [(String, String)]
-> IO ExitCode
rawSystemExitCode :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Char]
-> [[Char]]
-> Maybe [([Char], [Char])]
-> IO ExitCode
rawSystemExitCode Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Char]
path [[Char]]
args Maybe [([Char], [Char])]
menv =
(HasCallStack => IO ExitCode) -> IO ExitCode
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ExitCode) -> IO ExitCode)
-> (HasCallStack => IO ExitCode) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$
Verbosity -> CreateProcess -> IO ExitCode
rawSystemProc Verbosity
verbosity (CreateProcess -> IO ExitCode) -> CreateProcess -> IO ExitCode
forall a b. (a -> b) -> a -> b
$
([Char] -> [[Char]] -> CreateProcess
proc [Char]
path [[Char]]
args)
{ Process.cwd = fmap getSymbolicPath mbWorkDir
, Process.env = menv
}
rawSystemProc :: Verbosity -> Process.CreateProcess -> IO ExitCode
rawSystemProc :: Verbosity -> CreateProcess -> IO ExitCode
rawSystemProc Verbosity
verbosity CreateProcess
cp = (HasCallStack => IO ExitCode) -> IO ExitCode
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ExitCode) -> IO ExitCode)
-> (HasCallStack => IO ExitCode) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ do
(exitcode, _) <- Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ())
-> IO (ExitCode, ())
forall a.
Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
rawSystemProcAction Verbosity
verbosity CreateProcess
cp ((Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ())
-> IO (ExitCode, ()))
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ())
-> IO (ExitCode, ())
forall a b. (a -> b) -> a -> b
$ \Maybe Handle
_ Maybe Handle
_ Maybe Handle
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
return exitcode
rawSystemProcAction
:: Verbosity
-> Process.CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
rawSystemProcAction :: forall a.
Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
rawSystemProcAction Verbosity
verbosity CreateProcess
cp Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a
action = (HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a)
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a))
-> (HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a)
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> CreateProcess -> IO ()
logCommand Verbosity
verbosity CreateProcess
cp
(exitcode, a) <- CreateProcess
-> (Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> ProcessHandle
-> IO (ExitCode, a))
-> IO (ExitCode, a)
forall a.
CreateProcess
-> (Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a)
-> IO a
Process.withCreateProcess CreateProcess
cp ((Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> ProcessHandle
-> IO (ExitCode, a))
-> IO (ExitCode, a))
-> (Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> ProcessHandle
-> IO (ExitCode, a))
-> IO (ExitCode, a)
forall a b. (a -> b) -> a -> b
$ \Maybe Handle
mStdin Maybe Handle
mStdout Maybe Handle
mStderr ProcessHandle
p -> do
a <- Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a
action Maybe Handle
mStdin Maybe Handle
mStdout Maybe Handle
mStderr
exitcode <- Process.waitForProcess p
return (exitcode, a)
unless (exitcode == ExitSuccess) $ do
let cmd = case CreateProcess -> CmdSpec
Process.cmdspec CreateProcess
cp of
Process.ShellCommand [Char]
sh -> [Char]
sh
Process.RawCommand [Char]
path [[Char]]
_args -> [Char]
path
debug verbosity $ cmd ++ " returned " ++ show exitcode
return (exitcode, a)
fromCreatePipe :: Maybe Handle -> Handle
fromCreatePipe :: Maybe Handle -> Handle
fromCreatePipe = Handle -> (Handle -> Handle) -> Maybe Handle -> Handle
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Handle
forall a. HasCallStack => [Char] -> a
error [Char]
"fromCreatePipe: Nothing") Handle -> Handle
forall a. a -> a
id
rawSystemExitWithEnv
:: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnv :: Verbosity -> [Char] -> [[Char]] -> [([Char], [Char])] -> IO ()
rawSystemExitWithEnv Verbosity
verbosity =
Verbosity
-> Maybe (SymbolicPath CWD (ZonkAny 7))
-> [Char]
-> [[Char]]
-> [([Char], [Char])]
-> IO ()
forall (to :: FileOrDir).
Verbosity
-> Maybe (SymbolicPath CWD to)
-> [Char]
-> [[Char]]
-> [([Char], [Char])]
-> IO ()
rawSystemExitWithEnvCwd Verbosity
verbosity Maybe (SymbolicPath CWD (ZonkAny 7))
forall a. Maybe a
Nothing
rawSystemExitWithEnvCwd
:: Verbosity
-> Maybe (SymbolicPath CWD to)
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnvCwd :: forall (to :: FileOrDir).
Verbosity
-> Maybe (SymbolicPath CWD to)
-> [Char]
-> [[Char]]
-> [([Char], [Char])]
-> IO ()
rawSystemExitWithEnvCwd Verbosity
verbosity Maybe (SymbolicPath CWD to)
mbWorkDir [Char]
path [[Char]]
args [([Char], [Char])]
env =
(HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
IO ExitCode -> IO ()
maybeExit (IO ExitCode -> IO ()) -> IO ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$
Verbosity -> CreateProcess -> IO ExitCode
rawSystemProc Verbosity
verbosity (CreateProcess -> IO ExitCode) -> CreateProcess -> IO ExitCode
forall a b. (a -> b) -> a -> b
$
([Char] -> [[Char]] -> CreateProcess
proc [Char]
path [[Char]]
args)
{ Process.env = Just env
, Process.cwd = getSymbolicPath <$> mbWorkDir
}
rawSystemIOWithEnv
:: Verbosity
-> FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ExitCode
rawSystemIOWithEnv :: Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ExitCode
rawSystemIOWithEnv Verbosity
verbosity [Char]
path [[Char]]
args Maybe [Char]
mcwd Maybe [([Char], [Char])]
menv Maybe Handle
inp Maybe Handle
out Maybe Handle
err = (HasCallStack => IO ExitCode) -> IO ExitCode
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ExitCode) -> IO ExitCode)
-> (HasCallStack => IO ExitCode) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ do
(exitcode, _) <-
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> IO ()
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, ())
forall a.
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> IO a
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, a)
rawSystemIOWithEnvAndAction
Verbosity
verbosity
[Char]
path
[[Char]]
args
Maybe [Char]
mcwd
Maybe [([Char], [Char])]
menv
IO ()
action
Maybe Handle
inp
Maybe Handle
out
Maybe Handle
err
return exitcode
where
action :: IO ()
action = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
rawSystemIOWithEnvAndAction
:: Verbosity
-> FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> IO a
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, a)
rawSystemIOWithEnvAndAction :: forall a.
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> IO a
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, a)
rawSystemIOWithEnvAndAction Verbosity
verbosity [Char]
path [[Char]]
args Maybe [Char]
mcwd Maybe [([Char], [Char])]
menv IO a
action Maybe Handle
inp Maybe Handle
out Maybe Handle
err = (HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a)
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a))
-> (HasCallStack => IO (ExitCode, a)) -> IO (ExitCode, a)
forall a b. (a -> b) -> a -> b
$ do
let cp :: CreateProcess
cp =
([Char] -> [[Char]] -> CreateProcess
proc [Char]
path [[Char]]
args)
{ Process.cwd = mcwd
, Process.env = menv
, Process.std_in = mbToStd inp
, Process.std_out = mbToStd out
, Process.std_err = mbToStd err
}
Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
forall a.
Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
rawSystemProcAction Verbosity
verbosity CreateProcess
cp (\Maybe Handle
_ Maybe Handle
_ Maybe Handle
_ -> IO a
action)
where
mbToStd :: Maybe Handle -> Process.StdStream
mbToStd :: Maybe Handle -> StdStream
mbToStd = StdStream -> (Handle -> StdStream) -> Maybe Handle -> StdStream
forall b a. b -> (a -> b) -> Maybe a -> b
maybe StdStream
Process.Inherit Handle -> StdStream
Process.UseHandle
rawSystemStdout :: forall mode. KnownIODataMode mode => Verbosity -> FilePath -> [String] -> IO mode
rawSystemStdout :: forall mode.
KnownIODataMode mode =>
Verbosity -> [Char] -> [[Char]] -> IO mode
rawSystemStdout Verbosity
verbosity [Char]
path [[Char]]
args = (HasCallStack => IO mode) -> IO mode
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO mode) -> IO mode)
-> (HasCallStack => IO mode) -> IO mode
forall a b. (a -> b) -> a -> b
$ do
(output, errors, exitCode) <-
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, [Char], ExitCode)
forall mode.
KnownIODataMode mode =>
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, [Char], ExitCode)
rawSystemStdInOut
Verbosity
verbosity
[Char]
path
[[Char]]
args
Maybe [Char]
forall a. Maybe a
Nothing
Maybe [([Char], [Char])]
forall a. Maybe a
Nothing
Maybe IOData
forall a. Maybe a
Nothing
(IODataMode mode
forall mode. KnownIODataMode mode => IODataMode mode
IOData.iodataMode :: IODataMode mode)
when (exitCode /= ExitSuccess) $
dieWithException verbosity $
RawSystemStdout errors
return output
rawSystemStdInOut
:: KnownIODataMode mode
=> Verbosity
-> FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, String, ExitCode)
rawSystemStdInOut :: forall mode.
KnownIODataMode mode =>
Verbosity
-> [Char]
-> [[Char]]
-> Maybe [Char]
-> Maybe [([Char], [Char])]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, [Char], ExitCode)
rawSystemStdInOut Verbosity
verbosity [Char]
path [[Char]]
args Maybe [Char]
mcwd Maybe [([Char], [Char])]
menv Maybe IOData
input IODataMode mode
_ = (HasCallStack => IO (mode, [Char], ExitCode))
-> IO (mode, [Char], ExitCode)
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO (mode, [Char], ExitCode))
-> IO (mode, [Char], ExitCode))
-> (HasCallStack => IO (mode, [Char], ExitCode))
-> IO (mode, [Char], ExitCode)
forall a b. (a -> b) -> a -> b
$ do
let cp :: CreateProcess
cp =
([Char] -> [[Char]] -> CreateProcess
proc [Char]
path [[Char]]
args)
{ Process.cwd = mcwd
, Process.env = menv
, Process.std_in = Process.CreatePipe
, Process.std_out = Process.CreatePipe
, Process.std_err = Process.CreatePipe
}
(exitcode, (mberr1, mberr2)) <- Verbosity
-> CreateProcess
-> (Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException [Char]))
forall a.
Verbosity
-> CreateProcess
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a)
-> IO (ExitCode, a)
rawSystemProcAction Verbosity
verbosity CreateProcess
cp ((Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException [Char])))
-> (Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException [Char]))
forall a b. (a -> b) -> a -> b
$ \Maybe Handle
mb_in Maybe Handle
mb_out Maybe Handle
mb_err -> do
let (Handle
inh, Handle
outh, Handle
errh) = (Maybe Handle -> Handle
fromCreatePipe Maybe Handle
mb_in, Maybe Handle -> Handle
fromCreatePipe Maybe Handle
mb_out, Maybe Handle -> Handle
fromCreatePipe Maybe Handle
mb_err)
(IO (Either SomeException mode, Either SomeException [Char])
-> IO ()
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO ()
-> IO (Either SomeException mode, Either SomeException [Char])
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Either SomeException mode, Either SomeException [Char])
-> IO ()
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. IO a -> IO b -> IO a
Exception.finally (Handle -> IO ()
hClose Handle
inh IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
outh IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
errh) (IO (Either SomeException mode, Either SomeException [Char])
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char])
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. (a -> b) -> a -> b
$ do
Handle -> Bool -> IO ()
hSetBinaryMode Handle
errh Bool
False
IO [Char]
-> (AsyncM [Char]
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. NFData a => IO a -> (AsyncM a -> IO b) -> IO b
withAsyncNF (Handle -> IO [Char]
hGetContents Handle
errh) ((AsyncM [Char]
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char]))
-> (AsyncM [Char]
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. (a -> b) -> a -> b
$ \AsyncM [Char]
errA -> IO mode
-> (AsyncM mode
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. NFData a => IO a -> (AsyncM a -> IO b) -> IO b
withAsyncNF (Handle -> IO mode
forall mode. KnownIODataMode mode => Handle -> IO mode
IOData.hGetIODataContents Handle
outh) ((AsyncM mode
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char]))
-> (AsyncM mode
-> IO (Either SomeException mode, Either SomeException [Char]))
-> IO (Either SomeException mode, Either SomeException [Char])
forall a b. (a -> b) -> a -> b
$ \AsyncM mode
outA -> do
IO () -> IO ()
ignoreSigPipe (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ case Maybe IOData
input of
Maybe IOData
Nothing -> Handle -> IO ()
hClose Handle
inh
Just IOData
inputData -> Handle -> IOData -> IO ()
IOData.hPutContents Handle
inh IOData
inputData
mberr1 <- AsyncM mode -> IO (Either SomeException mode)
forall a. AsyncM a -> IO (Either SomeException a)
waitCatch AsyncM mode
outA
mberr2 <- waitCatch errA
return (mberr1, mberr2)
err <- reportOutputIOError mberr2
unless (exitcode == ExitSuccess) $
debug verbosity $
path
++ " returned "
++ show exitcode
++ if null err
then ""
else
" with error message:\n"
++ err
++ case input of
Maybe IOData
Nothing -> [Char]
""
Just IOData
d | IOData -> Bool
IOData.null IOData
d -> [Char]
""
Just (IODataText [Char]
inp) -> [Char]
"\nstdin input:\n" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
inp
Just (IODataBinary ByteString
inp) -> [Char]
"\nstdin input (binary):\n" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ByteString -> [Char]
forall a. Show a => a -> [Char]
show ByteString
inp
out <- reportOutputIOError mberr1
return (out, err, exitcode)
where
reportOutputIOError :: Either Exception.SomeException a -> IO a
reportOutputIOError :: forall a. Either SomeException a -> IO a
reportOutputIOError (Right a
x) = a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
reportOutputIOError (Left SomeException
exc) = case SomeException -> Maybe IOException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
exc of
Just IOException
ioe -> IOException -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO (IOException -> [Char] -> IOException
ioeSetFileName IOException
ioe ([Char]
"output of " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path))
Maybe IOException
Nothing -> SomeException -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO SomeException
exc
ignoreSigPipe :: IO () -> IO ()
ignoreSigPipe :: IO () -> IO ()
ignoreSigPipe = (IOException -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Exception.handle ((IOException -> IO ()) -> IO () -> IO ())
-> (IOException -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ \case
GHC.IOError{ioe_type :: IOException -> IOErrorType
GHC.ioe_type = IOErrorType
GHC.ResourceVanished, ioe_errno :: IOException -> Maybe CInt
GHC.ioe_errno = Just CInt
ioe}
| CInt -> Errno
Errno CInt
ioe Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
ePIPE -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
IOException
e -> IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO IOException
e
findProgramVersion
:: String
-> (String -> String)
-> Verbosity
-> FilePath
-> IO (Maybe Version)
findProgramVersion :: [Char]
-> ([Char] -> [Char]) -> Verbosity -> [Char] -> IO (Maybe Version)
findProgramVersion [Char]
versionArg [Char] -> [Char]
selectVersion Verbosity
verbosity [Char]
path = (HasCallStack => IO (Maybe Version)) -> IO (Maybe Version)
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO (Maybe Version)) -> IO (Maybe Version))
-> (HasCallStack => IO (Maybe Version)) -> IO (Maybe Version)
forall a b. (a -> b) -> a -> b
$ do
str <-
Verbosity -> [Char] -> [[Char]] -> IO [Char]
forall mode.
KnownIODataMode mode =>
Verbosity -> [Char] -> [[Char]] -> IO mode
rawSystemStdout Verbosity
verbosity [Char]
path [[Char]
versionArg]
IO [Char] -> (IOException -> IO [Char]) -> IO [Char]
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` (\IOException
_ -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"")
IO [Char]
-> (VerboseException CabalException -> IO [Char]) -> IO [Char]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(VerboseException CabalException
_ :: VerboseException CabalException) -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"")
IO [Char] -> (ExitCode -> IO [Char]) -> IO [Char]
forall a. IO a -> (ExitCode -> IO a) -> IO a
`catchExit` (\ExitCode
_ -> [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"")
let version :: Maybe Version
version = [Char] -> Maybe Version
forall a. Parsec a => [Char] -> Maybe a
simpleParsec ([Char] -> [Char]
selectVersion [Char]
str)
case version of
Maybe Version
Nothing ->
Verbosity -> [Char] -> IO ()
warn Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char]
"cannot determine version of "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" :\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
str
Just Version
v -> Verbosity -> [Char] -> IO ()
debug Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
path [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is version " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Version -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Version
v
return version
xargs
:: Int
-> ([String] -> IO ())
-> [String]
-> [String]
-> IO ()
xargs :: Int -> ([[Char]] -> IO ()) -> [[Char]] -> [[Char]] -> IO ()
xargs Int
maxSize [[Char]] -> IO ()
rawSystemFun [[Char]]
fixedArgs [[Char]]
bigArgs =
let fixedArgSize :: Int
fixedArgSize = [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (([Char] -> Int) -> [[Char]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Char]]
fixedArgs) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [[Char]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Char]]
fixedArgs
chunkSize :: Int
chunkSize = Int
maxSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
fixedArgSize
in ([[Char]] -> IO ()) -> [[[Char]]] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ ([[Char]] -> IO ()
rawSystemFun ([[Char]] -> IO ()) -> ([[Char]] -> [[Char]]) -> [[Char]] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]]
fixedArgs [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++)) (Int -> [[Char]] -> [[[Char]]]
forall {t :: * -> *} {a}. Foldable t => Int -> [t a] -> [[t a]]
chunks Int
chunkSize [[Char]]
bigArgs)
where
chunks :: Int -> [t a] -> [[t a]]
chunks Int
len = ([t a] -> Maybe ([t a], [t a])) -> [t a] -> [[t a]]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr (([t a] -> Maybe ([t a], [t a])) -> [t a] -> [[t a]])
-> ([t a] -> Maybe ([t a], [t a])) -> [t a] -> [[t a]]
forall a b. (a -> b) -> a -> b
$ \[t a]
s ->
if [t a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t a]
s
then Maybe ([t a], [t a])
forall a. Maybe a
Nothing
else ([t a], [t a]) -> Maybe ([t a], [t a])
forall a. a -> Maybe a
Just ([t a] -> Int -> [t a] -> ([t a], [t a])
forall {t :: * -> *} {a}.
Foldable t =>
[t a] -> Int -> [t a] -> ([t a], [t a])
chunk [] Int
len [t a]
s)
chunk :: [t a] -> Int -> [t a] -> ([t a], [t a])
chunk [t a]
acc Int
_ [] = ([t a] -> [t a]
forall a. [a] -> [a]
reverse [t a]
acc, [])
chunk [t a]
acc Int
len (t a
s : [t a]
ss)
| Int
len' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len = [t a] -> Int -> [t a] -> ([t a], [t a])
chunk (t a
s t a -> [t a] -> [t a]
forall a. a -> [a] -> [a]
: [t a]
acc) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
len' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [t a]
ss
| Bool
otherwise = ([t a] -> [t a]
forall a. [a] -> [a]
reverse [t a]
acc, t a
s t a -> [t a] -> [t a]
forall a. a -> [a] -> [a]
: [t a]
ss)
where
len' :: Int
len' = t a -> Int
forall a. t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
s
findFileCwd
:: forall searchDir allowAbsolute
. Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (SymbolicPathX allowAbsolute Pkg File)
findFileCwd :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
findFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath SymbolicPathX 'OnlyRelative searchDir 'File
fileName =
(SymbolicPathX allowAbsolute Pkg 'File -> [Char])
-> [SymbolicPathX allowAbsolute Pkg 'File]
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
forall a. (a -> [Char]) -> [a] -> IO (Maybe a)
findFirstFile
(Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir)
[ SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative searchDir 'File
fileName
| SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path <- [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
forall a. Ord a => [a] -> [a]
ordNub [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath
]
IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
-> (Maybe (SymbolicPathX allowAbsolute Pkg 'File)
-> IO (SymbolicPathX allowAbsolute Pkg 'File))
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO (SymbolicPathX allowAbsolute Pkg 'File)
-> (SymbolicPathX allowAbsolute Pkg 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File))
-> Maybe (SymbolicPathX allowAbsolute Pkg 'File)
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Verbosity
-> CabalException -> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO (SymbolicPathX allowAbsolute Pkg 'File))
-> CabalException -> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall a b. (a -> b) -> a -> b
$ [Char] -> CabalException
FindFile ([Char] -> CabalException) -> [Char] -> CabalException
forall a b. (a -> b) -> a -> b
$ SymbolicPathX 'OnlyRelative searchDir 'File -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath SymbolicPathX 'OnlyRelative searchDir 'File
fileName) SymbolicPathX allowAbsolute Pkg 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
findFileEx
:: forall searchDir allowAbsolute
. Verbosity
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (SymbolicPathX allowAbsolute Pkg File)
findFileEx :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
findFileEx Verbosity
v = Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
findFileCwd Verbosity
v Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findFileWithExtension
:: [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg File))
findFileWithExtension :: forall (allowAbsolute :: AllowAbsolute) searchDir.
[Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
findFileWithExtension =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
findFileCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findFileCwdWithExtension
:: forall searchDir allowAbsolute
. Maybe (SymbolicPath CWD (Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg File))
findFileCwdWithExtension :: forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
findFileCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [Suffix]
extensions [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath RelativePath searchDir 'File
baseName =
((SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> SymbolicPathX allowAbsolute Pkg 'File)
-> Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> Maybe (SymbolicPathX allowAbsolute Pkg 'File)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File)
-> (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> SymbolicPathX allowAbsolute Pkg 'File
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
(</>))
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> Maybe (SymbolicPathX allowAbsolute Pkg 'File))
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileCwdWithExtension' Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [Suffix]
extensions [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath RelativePath searchDir 'File
baseName
findAllFilesCwdWithExtension
:: forall searchDir allowAbsolute
. Maybe (SymbolicPath CWD (Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO [SymbolicPathX allowAbsolute Pkg File]
findAllFilesCwdWithExtension :: forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
findAllFilesCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Suffix]
extensions [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath SymbolicPathX 'OnlyRelative searchDir 'File
basename =
(SymbolicPathX allowAbsolute Pkg 'File -> [Char])
-> [SymbolicPathX allowAbsolute Pkg 'File]
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
forall a. (a -> [Char]) -> [a] -> IO [a]
findAllFiles
(Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir)
[ SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative searchDir 'File
basename SymbolicPathX 'OnlyRelative searchDir 'File
-> [Char] -> SymbolicPathX 'OnlyRelative searchDir 'File
forall p. FileLike p => p -> [Char] -> p
<.> [Char]
ext
| SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path <- [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
forall a. Ord a => [a] -> [a]
ordNub [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath
, Suffix [Char]
ext <- [Suffix] -> [Suffix]
forall a. Ord a => [a] -> [a]
ordNub [Suffix]
extensions
]
findAllFilesWithExtension
:: [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO [SymbolicPathX allowAbsolute Pkg File]
findAllFilesWithExtension :: forall (allowAbsolute :: AllowAbsolute) searchDir.
[Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
findAllFilesWithExtension =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
findAllFilesCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findFileWithExtension'
:: [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File))
findFileWithExtension' :: forall (allowAbsolute :: AllowAbsolute) searchDir.
[Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileWithExtension' =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileCwdWithExtension' Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findFileCwdWithExtension'
:: forall searchDir allowAbsolute
. Maybe (SymbolicPath CWD (Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> RelativePath searchDir File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File))
findFileCwdWithExtension' :: forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileCwdWithExtension' Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [Suffix]
extensions [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath SymbolicPathX 'OnlyRelative searchDir 'File
baseName =
((SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
SymbolicPathX 'OnlyRelative searchDir 'File)
-> [Char])
-> [(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
SymbolicPathX 'OnlyRelative searchDir 'File)]
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
SymbolicPathX 'OnlyRelative searchDir 'File))
forall a. (a -> [Char]) -> [a] -> IO (Maybe a)
findFirstFile
((SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File -> [Char])
-> (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
SymbolicPathX 'OnlyRelative searchDir 'File)
-> [Char]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File -> [Char]
mkPath)
[ (SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path, SymbolicPathX 'OnlyRelative searchDir 'File
baseName SymbolicPathX 'OnlyRelative searchDir 'File
-> [Char] -> SymbolicPathX 'OnlyRelative searchDir 'File
forall p. FileLike p => p -> [Char] -> p
<.> [Char]
ext)
| SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path <- [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
forall a. Ord a => [a] -> [a]
ordNub [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath
, Suffix [Char]
ext <- [Suffix] -> [Suffix]
forall a. Ord a => [a] -> [a]
ordNub [Suffix]
extensions
]
where
mkPath :: SymbolicPathX allowAbsolute Pkg (Dir searchDir) -> RelativePath searchDir File -> FilePath
mkPath :: SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File -> [Char]
mkPath SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
base SymbolicPathX 'OnlyRelative searchDir 'File
file =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
cwd (SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
base SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> SymbolicPathX 'OnlyRelative searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative searchDir 'File
file)
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile :: forall a. (a -> [Char]) -> [a] -> IO (Maybe a)
findFirstFile a -> [Char]
file = [a] -> IO (Maybe a)
findFirst
where
findFirst :: [a] -> IO (Maybe a)
findFirst [] = Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
findFirst (a
x : [a]
xs) = do
exists <- [Char] -> IO Bool
doesFileExist (a -> [Char]
file a
x)
if exists
then return (Just x)
else findFirst xs
findAllFiles :: (a -> FilePath) -> [a] -> IO [a]
findAllFiles :: forall a. (a -> [Char]) -> [a] -> IO [a]
findAllFiles a -> [Char]
file = (a -> IO Bool) -> [a] -> IO [a]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM ([Char] -> IO Bool
doesFileExist ([Char] -> IO Bool) -> (a -> [Char]) -> a -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Char]
file)
findModuleFilesEx
:: forall searchDir allowAbsolute
. Verbosity
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> [Suffix]
-> [ModuleName]
-> IO [(SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)]
findModuleFilesEx :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> [ModuleName]
-> IO
[(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
findModuleFilesEx Verbosity
verbosity [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath [Suffix]
extensions [ModuleName]
moduleNames =
(ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
-> [ModuleName]
-> IO
[(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (Verbosity
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
findModuleFileEx Verbosity
verbosity [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath [Suffix]
extensions) [ModuleName]
moduleNames
findModuleFilesCwd
:: forall searchDir allowAbsolute
. Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> [Suffix]
-> [ModuleName]
-> IO [(SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)]
findModuleFilesCwd :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> [ModuleName]
-> IO
[(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
findModuleFilesCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath [Suffix]
extensions [ModuleName]
moduleNames =
(ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
-> [ModuleName]
-> IO
[(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
findModuleFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath [Suffix]
extensions) [ModuleName]
moduleNames
findModuleFileEx
:: forall searchDir allowAbsolute
. Verbosity
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)
findModuleFileEx :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
findModuleFileEx Verbosity
verbosity =
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
findModuleFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findModuleFileCwd
:: forall searchDir allowAbsolute
. Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)
findModuleFileCwd :: forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> ModuleName
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
findModuleFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
cwd [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath [Suffix]
extensions ModuleName
mod_name = do
mbRes <-
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileCwdWithExtension'
Maybe (SymbolicPath CWD ('Dir Pkg))
cwd
[Suffix]
extensions
[SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath
([Char] -> RelativePath searchDir 'File
forall from (to :: FileOrDir).
HasCallStack =>
[Char] -> RelativePath from to
makeRelativePathEx ([Char] -> RelativePath searchDir 'File)
-> [Char] -> RelativePath searchDir 'File
forall a b. (a -> b) -> a -> b
$ ModuleName -> [Char]
ModuleName.toFilePath ModuleName
mod_name)
case mbRes of
Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
Nothing ->
Verbosity
-> CabalException
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
-> CabalException
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall a b. (a -> b) -> a -> b
$
ModuleName -> [Suffix] -> [[Char]] -> CabalException
FindModuleFileEx ModuleName
mod_name [Suffix]
extensions ((SymbolicPathX allowAbsolute Pkg ('Dir searchDir) -> [Char])
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX allowAbsolute Pkg ('Dir searchDir) -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
searchPath)
Just (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
res -> (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> IO
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
res
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive :: [Char] -> IO [[Char]]
getDirectoryContentsRecursive [Char]
topdir = [[Char]] -> IO [[Char]]
recurseDirectories [[Char]
""]
where
recurseDirectories :: [FilePath] -> IO [FilePath]
recurseDirectories :: [[Char]] -> IO [[Char]]
recurseDirectories [] = [[Char]] -> IO [[Char]]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
recurseDirectories ([Char]
dir : [[Char]]
dirs) = IO [[Char]] -> IO [[Char]]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [[Char]] -> IO [[Char]]) -> IO [[Char]] -> IO [[Char]]
forall a b. (a -> b) -> a -> b
$ do
(files, dirs') <- [[Char]] -> [[Char]] -> [[Char]] -> IO ([[Char]], [[Char]])
collect [] [] ([[Char]] -> IO ([[Char]], [[Char]]))
-> IO [[Char]] -> IO ([[Char]], [[Char]])
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Char] -> IO [[Char]]
getDirectoryContents ([Char]
topdir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
dir)
files' <- recurseDirectories (dirs' ++ dirs)
return (files ++ files')
where
collect :: [[Char]] -> [[Char]] -> [[Char]] -> IO ([[Char]], [[Char]])
collect [[Char]]
files [[Char]]
dirs' [] =
([[Char]], [[Char]]) -> IO ([[Char]], [[Char]])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
( [[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse [[Char]]
files
, [[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse [[Char]]
dirs'
)
collect [[Char]]
files [[Char]]
dirs' ([Char]
entry : [[Char]]
entries)
| [Char] -> Bool
ignore [Char]
entry =
[[Char]] -> [[Char]] -> [[Char]] -> IO ([[Char]], [[Char]])
collect [[Char]]
files [[Char]]
dirs' [[Char]]
entries
collect [[Char]]
files [[Char]]
dirs' ([Char]
entry : [[Char]]
entries) = do
let dirEntry :: [Char]
dirEntry = [Char]
dir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
entry
isDirectory <- [Char] -> IO Bool
doesDirectoryExist ([Char]
topdir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
dirEntry)
if isDirectory
then collect files (dirEntry : dirs') entries
else collect (dirEntry : files) dirs' entries
ignore :: [Char] -> Bool
ignore [Char
'.'] = Bool
True
ignore [Char
'.', Char
'.'] = Bool
True
ignore [Char]
_ = Bool
False
isInSearchPath :: FilePath -> IO Bool
isInSearchPath :: [Char] -> IO Bool
isInSearchPath [Char]
path = ([[Char]] -> Bool) -> IO [[Char]] -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Char] -> [[Char]] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem [Char]
path) IO [[Char]]
getSearchPath
addLibraryPath
:: OS
-> [FilePath]
-> [(String, String)]
-> [(String, String)]
addLibraryPath :: OS -> [[Char]] -> [([Char], [Char])] -> [([Char], [Char])]
addLibraryPath OS
os [[Char]]
paths = [([Char], [Char])] -> [([Char], [Char])]
addEnv
where
pathsString :: [Char]
pathsString = [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char
searchPathSeparator] [[Char]]
paths
ldPath :: [Char]
ldPath = case OS
os of
OS
OSX -> [Char]
"DYLD_LIBRARY_PATH"
OS
_ -> [Char]
"LD_LIBRARY_PATH"
addEnv :: [([Char], [Char])] -> [([Char], [Char])]
addEnv [] = [([Char]
ldPath, [Char]
pathsString)]
addEnv (([Char]
key, [Char]
value) : [([Char], [Char])]
xs)
| [Char]
key [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
ldPath =
if [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
value
then ([Char]
key, [Char]
pathsString) ([Char], [Char]) -> [([Char], [Char])] -> [([Char], [Char])]
forall a. a -> [a] -> [a]
: [([Char], [Char])]
xs
else ([Char]
key, [Char]
value [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (Char
searchPathSeparator Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
pathsString)) ([Char], [Char]) -> [([Char], [Char])] -> [([Char], [Char])]
forall a. a -> [a] -> [a]
: [([Char], [Char])]
xs
| Bool
otherwise = ([Char]
key, [Char]
value) ([Char], [Char]) -> [([Char], [Char])] -> [([Char], [Char])]
forall a. a -> [a] -> [a]
: [([Char], [Char])] -> [([Char], [Char])]
addEnv [([Char], [Char])]
xs
moreRecentFile :: FilePath -> FilePath -> IO Bool
moreRecentFile :: [Char] -> [Char] -> IO Bool
moreRecentFile [Char]
a [Char]
b = do
exists <- [Char] -> IO Bool
doesFileExist [Char]
b
if not exists
then return True
else do
tb <- getModificationTime b
ta <- getModificationTime a
return (ta > tb)
existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool
existsAndIsMoreRecentThan :: [Char] -> [Char] -> IO Bool
existsAndIsMoreRecentThan [Char]
a [Char]
b = do
exists <- [Char] -> IO Bool
doesFileExist [Char]
a
if not exists
then return False
else a `moreRecentFile` b
createDirectoryIfMissingVerbose
:: Verbosity
-> Bool
-> FilePath
-> IO ()
createDirectoryIfMissingVerbose :: Verbosity -> Bool -> [Char] -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
create_parents [Char]
path0
| Bool
create_parents = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ [[Char]] -> IO ()
createDirs ([Char] -> [[Char]]
parents [Char]
path0)
| Bool
otherwise = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ [[Char]] -> IO ()
createDirs (Int -> [[Char]] -> [[Char]]
forall a. Int -> [a] -> [a]
take Int
1 ([Char] -> [[Char]]
parents [Char]
path0))
where
parents :: [Char] -> [[Char]]
parents = [[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
(</>) ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
splitDirectories ([Char] -> [[Char]]) -> ([Char] -> [Char]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
normalise
createDirs :: [[Char]] -> IO ()
createDirs [] = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
createDirs ([Char]
dir : []) = [Char] -> (IOException -> IO ()) -> IO ()
createDir [Char]
dir IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO
createDirs ([Char]
dir : [[Char]]
dirs) =
[Char] -> (IOException -> IO ()) -> IO ()
createDir [Char]
dir ((IOException -> IO ()) -> IO ())
-> (IOException -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IOException
_ -> do
[[Char]] -> IO ()
createDirs [[Char]]
dirs
[Char] -> (IOException -> IO ()) -> IO ()
createDir [Char]
dir IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO
createDir :: FilePath -> (IOException -> IO ()) -> IO ()
createDir :: [Char] -> (IOException -> IO ()) -> IO ()
createDir [Char]
dir IOException -> IO ()
notExistHandler = do
r <- IO () -> IO (Either IOException ())
forall a. IO a -> IO (Either IOException a)
tryIO (IO () -> IO (Either IOException ()))
-> IO () -> IO (Either IOException ())
forall a b. (a -> b) -> a -> b
$ Verbosity -> [Char] -> IO ()
createDirectoryVerbose Verbosity
verbosity [Char]
dir
case (r :: Either IOException ()) of
Right () -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Left IOException
e
| IOException -> Bool
isDoesNotExistError IOException
e -> IOException -> IO ()
notExistHandler IOException
e
| IOException -> Bool
isAlreadyExistsError IOException
e ->
( do
isDir <- [Char] -> IO Bool
doesDirectoryExist [Char]
dir
unless isDir $ throwIO e
)
IO () -> (IOException -> IO ()) -> IO ()
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` ((\IOException
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) :: IOException -> IO ())
| Bool
otherwise -> IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO IOException
e
createDirectoryVerbose :: Verbosity -> FilePath -> IO ()
createDirectoryVerbose :: Verbosity -> [Char] -> IO ()
createDirectoryVerbose Verbosity
verbosity [Char]
dir = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"creating " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir
[Char] -> IO ()
createDirectory [Char]
dir
[Char] -> IO ()
setDirOrdinary [Char]
dir
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose :: Verbosity -> [Char] -> [Char] -> IO ()
copyFileVerbose Verbosity
verbosity [Char]
src [Char]
dest = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char]
"copy " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
src [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dest)
[Char] -> [Char] -> IO ()
copyFile [Char]
src [Char]
dest
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile :: Verbosity -> [Char] -> [Char] -> IO ()
installOrdinaryFile Verbosity
verbosity [Char]
src [Char]
dest = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char]
"Installing " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
src [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dest)
[Char] -> [Char] -> IO ()
copyOrdinaryFile [Char]
src [Char]
dest
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile :: Verbosity -> [Char] -> [Char] -> IO ()
installExecutableFile Verbosity
verbosity [Char]
src [Char]
dest = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char]
"Installing executable " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
src [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dest)
[Char] -> [Char] -> IO ()
copyExecutableFile [Char]
src [Char]
dest
installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installMaybeExecutableFile :: Verbosity -> [Char] -> [Char] -> IO ()
installMaybeExecutableFile Verbosity
verbosity [Char]
src [Char]
dest = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
perms <- [Char] -> IO Permissions
getPermissions [Char]
src
if (executable perms)
then installExecutableFile verbosity src dest
else installOrdinaryFile verbosity src dest
copyFileTo
:: Verbosity
-> FilePath
-> FilePath
-> IO ()
copyFileTo :: Verbosity -> [Char] -> [Char] -> IO ()
copyFileTo Verbosity
verbosity [Char]
dir [Char]
file =
(HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir (ZonkAny 6))
-> RelativePath Pkg 'File
-> IO ()
forall target.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir target)
-> RelativePath Pkg 'File
-> IO ()
copyFileToCwd
Verbosity
verbosity
Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
([Char] -> SymbolicPath Pkg ('Dir (ZonkAny 6))
forall from (to :: FileOrDir). [Char] -> SymbolicPath from to
makeSymbolicPath [Char]
dir)
([Char] -> RelativePath Pkg 'File
forall from (to :: FileOrDir).
HasCallStack =>
[Char] -> RelativePath from to
makeRelativePathEx [Char]
file)
copyFileToCwd
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir target)
-> RelativePath Pkg File
-> IO ()
copyFileToCwd :: forall target.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir target)
-> RelativePath Pkg 'File
-> IO ()
copyFileToCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir target)
dir RelativePath Pkg 'File
file = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let targetFile :: [Char]
targetFile = SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> [Char]
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> [Char]
i (SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> [Char])
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> [Char]
forall a b. (a -> b) -> a -> b
$ SymbolicPath Pkg ('Dir target)
dir SymbolicPath Pkg ('Dir target)
-> SymbolicPathX 'OnlyRelative target (ZonkAny 5)
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5)
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath Pkg 'File
-> SymbolicPathX 'OnlyRelative target (ZonkAny 5)
forall (allowAbsolute :: AllowAbsolute) from1 (to1 :: FileOrDir)
from2 (to2 :: FileOrDir).
SymbolicPathX allowAbsolute from1 to1
-> SymbolicPathX allowAbsolute from2 to2
unsafeCoerceSymbolicPath RelativePath Pkg 'File
file
Verbosity -> Bool -> [Char] -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True ([Char] -> [Char]
takeDirectory [Char]
targetFile)
Verbosity -> [Char] -> [Char] -> IO ()
installOrdinaryFile Verbosity
verbosity (RelativePath Pkg 'File -> [Char]
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> [Char]
i RelativePath Pkg 'File
file) [Char]
targetFile
where
i :: SymbolicPathX allowAbs Pkg to -> FilePath
i :: forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> [Char]
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbs Pkg to -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
copyFilesWith
:: (Verbosity -> FilePath -> FilePath -> IO ())
-> Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
copyFilesWith :: (Verbosity -> [Char] -> [Char] -> IO ())
-> Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFilesWith Verbosity -> [Char] -> [Char] -> IO ()
doCopy Verbosity
verbosity [Char]
targetDir [([Char], [Char])]
srcFiles = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let dirs :: [[Char]]
dirs = ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char]
targetDir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</>) ([[Char]] -> [[Char]])
-> ([([Char], [Char])] -> [[Char]])
-> [([Char], [Char])]
-> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
forall a. Ord a => [a] -> [a]
ordNub ([[Char]] -> [[Char]])
-> ([([Char], [Char])] -> [[Char]])
-> [([Char], [Char])]
-> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([Char], [Char]) -> [Char]) -> [([Char], [Char])] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char]
takeDirectory ([Char] -> [Char])
-> (([Char], [Char]) -> [Char]) -> ([Char], [Char]) -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char], [Char]) -> [Char]
forall a b. (a, b) -> b
snd) ([([Char], [Char])] -> [[Char]]) -> [([Char], [Char])] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [([Char], [Char])]
srcFiles
([Char] -> IO ()) -> [[Char]] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Verbosity -> Bool -> [Char] -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True) [[Char]]
dirs
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ let src :: [Char]
src = [Char]
srcBase [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
srcFile
dest :: [Char]
dest = [Char]
targetDir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
srcFile
in Verbosity -> [Char] -> [Char] -> IO ()
doCopy Verbosity
verbosity [Char]
src [Char]
dest
| ([Char]
srcBase, [Char]
srcFile) <- [([Char], [Char])]
srcFiles
]
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles :: Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFiles Verbosity
v [Char]
fp [([Char], [Char])]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> [Char] -> [Char] -> IO ())
-> Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFilesWith Verbosity -> [Char] -> [Char] -> IO ()
copyFileVerbose Verbosity
v [Char]
fp [([Char], [Char])]
fs)
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles :: Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
installOrdinaryFiles Verbosity
v [Char]
fp [([Char], [Char])]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> [Char] -> [Char] -> IO ())
-> Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFilesWith Verbosity -> [Char] -> [Char] -> IO ()
installOrdinaryFile Verbosity
v [Char]
fp [([Char], [Char])]
fs)
installExecutableFiles
:: Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
installExecutableFiles :: Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
installExecutableFiles Verbosity
v [Char]
fp [([Char], [Char])]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> [Char] -> [Char] -> IO ())
-> Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFilesWith Verbosity -> [Char] -> [Char] -> IO ()
installExecutableFile Verbosity
v [Char]
fp [([Char], [Char])]
fs)
installMaybeExecutableFiles
:: Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
installMaybeExecutableFiles :: Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
installMaybeExecutableFiles Verbosity
v [Char]
fp [([Char], [Char])]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> [Char] -> [Char] -> IO ())
-> Verbosity -> [Char] -> [([Char], [Char])] -> IO ()
copyFilesWith Verbosity -> [Char] -> [Char] -> IO ()
installMaybeExecutableFile Verbosity
v [Char]
fp [([Char], [Char])]
fs)
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents :: Verbosity -> [Char] -> [Char] -> IO ()
installDirectoryContents Verbosity
verbosity [Char]
srcDir [Char]
destDir = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char]
"copy directory '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
srcDir [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' to '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
destDir [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'.")
srcFiles <- [Char] -> IO [[Char]]
getDirectoryContentsRecursive [Char]
srcDir
installOrdinaryFiles verbosity destDir [(srcDir, f) | f <- srcFiles]
copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursive :: Verbosity -> [Char] -> [Char] -> IO ()
copyDirectoryRecursive Verbosity
verbosity [Char]
srcDir [Char]
destDir = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO ()) -> IO ())
-> (HasCallStack => IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> [Char] -> IO ()
info Verbosity
verbosity ([Char]
"copy directory '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
srcDir [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' to '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
destDir [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'.")
srcFiles <- [Char] -> IO [[Char]]
getDirectoryContentsRecursive [Char]
srcDir
copyFilesWith
(const copyFile)
verbosity
destDir
[ (srcDir, f)
| f <- srcFiles
]
doesExecutableExist :: FilePath -> IO Bool
doesExecutableExist :: [Char] -> IO Bool
doesExecutableExist [Char]
f = do
exists <- [Char] -> IO Bool
doesFileExist [Char]
f
if exists
then do
perms <- getPermissions f
return (executable perms)
else return False
data TempFileOptions = TempFileOptions
{ TempFileOptions -> Bool
optKeepTempFiles :: Bool
}
defaultTempFileOptions :: TempFileOptions
defaultTempFileOptions :: TempFileOptions
defaultTempFileOptions = TempFileOptions{optKeepTempFiles :: Bool
optKeepTempFiles = Bool
False}
withTempFile
:: String
-> (FilePath -> Handle -> IO a)
-> IO a
withTempFile :: forall a. [Char] -> ([Char] -> Handle -> IO a) -> IO a
withTempFile [Char]
template [Char] -> Handle -> IO a
f = (HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a.
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileCwd [Char]
template ((SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a b. (a -> b) -> a -> b
$
\SymbolicPathX 'AllowAbsolute Pkg 'File
fp Handle
h -> [Char] -> Handle -> IO a
f (SymbolicPathX 'AllowAbsolute Pkg 'File -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath SymbolicPathX 'AllowAbsolute Pkg 'File
fp) Handle
h
withTempFileCwd
:: String
-> (SymbolicPath Pkg File -> Handle -> IO a)
-> IO a
withTempFileCwd :: forall a.
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileCwd = (HasCallStack =>
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack =>
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> (HasCallStack =>
[Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a b. (a -> b) -> a -> b
$ TempFileOptions
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a.
TempFileOptions
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileEx TempFileOptions
defaultTempFileOptions
withTempFileEx
:: forall a
. TempFileOptions
-> String
-> (SymbolicPath Pkg File -> Handle -> IO a)
-> IO a
withTempFileEx :: forall a.
TempFileOptions
-> [Char]
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileEx TempFileOptions
opts [Char]
template SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a
action = do
tmp <- IO [Char]
getTemporaryDirectory
withFrozenCallStack $
Exception.bracket
(openTempFile tmp template)
( \([Char]
name, Handle
handle) -> do
Handle -> IO ()
hClose Handle
handle
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (TempFileOptions -> Bool
optKeepTempFiles TempFileOptions
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
() -> IO () -> IO ()
forall a. a -> IO a -> IO a
handleDoesNotExist () (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char] -> IO ()
removeFile ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char]
name
)
(withLexicalCallStack (\([Char]
fn, Handle
h) -> SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a
action ([Char] -> [Char] -> SymbolicPathX 'AllowAbsolute Pkg 'File
mkRelToPkg [Char]
tmp [Char]
fn) Handle
h))
where
mkRelToPkg :: FilePath -> FilePath -> SymbolicPath Pkg File
mkRelToPkg :: [Char] -> [Char] -> SymbolicPathX 'AllowAbsolute Pkg 'File
mkRelToPkg [Char]
tmp [Char]
fp =
[Char] -> SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 0))
forall from (to :: FileOrDir). [Char] -> SymbolicPath from to
makeSymbolicPath [Char]
tmp SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 0))
-> SymbolicPathX 'OnlyRelative (ZonkAny 0) 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> [Char] -> SymbolicPathX 'OnlyRelative (ZonkAny 0) 'File
forall from (to :: FileOrDir).
HasCallStack =>
[Char] -> RelativePath from to
makeRelativePathEx ([Char] -> [Char]
takeFileName [Char]
fp)
withTempDirectory
:: Verbosity
-> FilePath
-> String
-> (FilePath -> IO a)
-> IO a
withTempDirectory :: forall a. Verbosity -> [Char] -> [Char] -> ([Char] -> IO a) -> IO a
withTempDirectory Verbosity
verb [Char]
targetDir [Char]
template [Char] -> IO a
f =
(HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir (ZonkAny 2))
-> [Char]
-> (SymbolicPath Pkg ('Dir (ZonkAny 1)) -> IO a)
-> IO a
forall tmpDir1 tmpDir2 a.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwd
Verbosity
verb
Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
([Char] -> SymbolicPath Pkg ('Dir (ZonkAny 2))
forall from (to :: FileOrDir). [Char] -> SymbolicPath from to
makeSymbolicPath [Char]
targetDir)
[Char]
template
([Char] -> IO a
f ([Char] -> IO a)
-> (SymbolicPath Pkg ('Dir (ZonkAny 1)) -> [Char])
-> SymbolicPath Pkg ('Dir (ZonkAny 1))
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg ('Dir (ZonkAny 1)) -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath)
withTempDirectoryCwd
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir tmpDir1)
-> String
-> (SymbolicPath Pkg (Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwd :: forall tmpDir1 tmpDir2 a.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir tmpDir1)
targetDir [Char]
template SymbolicPath Pkg ('Dir tmpDir2) -> IO a
f =
(HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
forall a tmpDir1 tmpDir2.
Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwdEx
Verbosity
verbosity
TempFileOptions
defaultTempFileOptions
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
SymbolicPath Pkg ('Dir tmpDir1)
targetDir
[Char]
template
((SymbolicPath Pkg ('Dir tmpDir2) -> HasCallStack => IO a)
-> WithCallStack (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
forall a b.
(a -> WithCallStack (IO b)) -> WithCallStack (a -> IO b)
withLexicalCallStack (\SymbolicPath Pkg ('Dir tmpDir2)
x -> SymbolicPath Pkg ('Dir tmpDir2) -> IO a
f SymbolicPath Pkg ('Dir tmpDir2)
x))
withTempDirectoryEx
:: Verbosity
-> TempFileOptions
-> FilePath
-> String
-> (FilePath -> IO a)
-> IO a
withTempDirectoryEx :: forall a.
Verbosity
-> TempFileOptions -> [Char] -> [Char] -> ([Char] -> IO a) -> IO a
withTempDirectoryEx Verbosity
verbosity TempFileOptions
opts [Char]
targetDir [Char]
template [Char] -> IO a
f =
(HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir (ZonkAny 4))
-> [Char]
-> (SymbolicPath Pkg ('Dir (ZonkAny 3)) -> IO a)
-> IO a
forall a tmpDir1 tmpDir2.
Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwdEx Verbosity
verbosity TempFileOptions
opts Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing ([Char] -> SymbolicPath Pkg ('Dir (ZonkAny 4))
forall from (to :: FileOrDir). [Char] -> SymbolicPath from to
makeSymbolicPath [Char]
targetDir) [Char]
template ((SymbolicPath Pkg ('Dir (ZonkAny 3)) -> IO a) -> IO a)
-> (SymbolicPath Pkg ('Dir (ZonkAny 3)) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
\SymbolicPath Pkg ('Dir (ZonkAny 3))
fp -> [Char] -> IO a
f (SymbolicPath Pkg ('Dir (ZonkAny 3)) -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath SymbolicPath Pkg ('Dir (ZonkAny 3))
fp)
withTempDirectoryCwdEx
:: forall a tmpDir1 tmpDir2
. Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir tmpDir1)
-> String
-> (SymbolicPath Pkg (Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwdEx :: forall a tmpDir1 tmpDir2.
Verbosity
-> TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> [Char]
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwdEx Verbosity
_verbosity TempFileOptions
opts Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir tmpDir1)
targetDir [Char]
template SymbolicPath Pkg ('Dir tmpDir2) -> IO a
f =
(HasCallStack => IO a) -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO a) -> IO a) -> (HasCallStack => IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
IO [Char] -> ([Char] -> IO ()) -> ([Char] -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket
([Char] -> [Char] -> IO [Char]
createTempDirectory (SymbolicPath Pkg ('Dir tmpDir1) -> [Char]
i SymbolicPath Pkg ('Dir tmpDir1)
targetDir) [Char]
template)
( \[Char]
tmpDirRelPath ->
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (TempFileOptions -> Bool
optKeepTempFiles TempFileOptions
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
() -> IO () -> IO ()
forall a. a -> IO a -> IO a
handleDoesNotExist () (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char] -> IO ()
removeDirectoryRecursive (SymbolicPath Pkg ('Dir tmpDir1) -> [Char]
i SymbolicPath Pkg ('Dir tmpDir1)
targetDir [Char] -> [Char] -> [Char]
forall p q r. PathLike p q r => p -> q -> r
</> [Char]
tmpDirRelPath)
)
(([Char] -> HasCallStack => IO a) -> WithCallStack ([Char] -> IO a)
forall a b.
(a -> WithCallStack (IO b)) -> WithCallStack (a -> IO b)
withLexicalCallStack (\[Char]
tmpDirRelPath -> SymbolicPath Pkg ('Dir tmpDir2) -> IO a
f (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> SymbolicPath Pkg ('Dir tmpDir2) -> IO a
forall a b. (a -> b) -> a -> b
$ SymbolicPath Pkg ('Dir tmpDir1)
targetDir SymbolicPath Pkg ('Dir tmpDir1)
-> SymbolicPathX 'OnlyRelative tmpDir1 ('Dir tmpDir2)
-> SymbolicPath Pkg ('Dir tmpDir2)
forall p q r. PathLike p q r => p -> q -> r
</> [Char] -> SymbolicPathX 'OnlyRelative tmpDir1 ('Dir tmpDir2)
forall from (to :: FileOrDir).
HasCallStack =>
[Char] -> RelativePath from to
makeRelativePathEx [Char]
tmpDirRelPath))
where
i :: SymbolicPath Pkg ('Dir tmpDir1) -> [Char]
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1) -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
rewriteFileEx :: Verbosity -> FilePath -> String -> IO ()
rewriteFileEx :: Verbosity -> [Char] -> [Char] -> IO ()
rewriteFileEx Verbosity
verbosity [Char]
path =
Verbosity -> [Char] -> ByteString -> IO ()
rewriteFileLBS Verbosity
verbosity [Char]
path (ByteString -> IO ()) -> ([Char] -> ByteString) -> [Char] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ByteString
toUTF8LBS
rewriteFileLBS :: Verbosity -> FilePath -> BS.ByteString -> IO ()
rewriteFileLBS :: Verbosity -> [Char] -> ByteString -> IO ()
rewriteFileLBS Verbosity
verbosity [Char]
path ByteString
newContent =
(IO () -> (IOException -> IO ()) -> IO ())
-> (IOException -> IO ()) -> IO () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO () -> (IOException -> IO ()) -> IO ()
forall a. IO a -> (IOException -> IO a) -> IO a
catchIO IOException -> IO ()
mightNotExist (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
existingContent <- Verbosity -> IO ByteString -> IO ByteString
forall a. Verbosity -> IO a -> IO a
annotateIO Verbosity
verbosity (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ByteString
BS.readFile [Char]
path
_ <- evaluate (BS.length existingContent)
unless (existingContent == newContent) $
annotateIO verbosity $
writeFileAtomic path newContent
where
mightNotExist :: IOException -> IO ()
mightNotExist IOException
e
| IOException -> Bool
isDoesNotExistError IOException
e =
Verbosity -> IO () -> IO ()
forall a. Verbosity -> IO a -> IO a
annotateIO Verbosity
verbosity (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString -> IO ()
writeFileAtomic [Char]
path ByteString
newContent
| Bool
otherwise =
IOException -> IO ()
forall a. HasCallStack => IOException -> IO a
ioError IOException
e
shortRelativePath :: FilePath -> FilePath -> FilePath
shortRelativePath :: [Char] -> [Char] -> [Char]
shortRelativePath [Char]
from [Char]
to =
case [[Char]] -> [[Char]] -> ([[Char]], [[Char]])
forall a. Eq a => [a] -> [a] -> ([a], [a])
dropCommonPrefix ([Char] -> [[Char]]
splitDirectories [Char]
from) ([Char] -> [[Char]]
splitDirectories [Char]
to) of
([[Char]]
stuff, [[Char]]
path) -> [[Char]] -> [Char]
joinPath (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char] -> [Char]
forall a b. a -> b -> a
const [Char]
"..") [[Char]]
stuff [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
path)
where
dropCommonPrefix :: Eq a => [a] -> [a] -> ([a], [a])
dropCommonPrefix :: forall a. Eq a => [a] -> [a] -> ([a], [a])
dropCommonPrefix (a
x : [a]
xs) (a
y : [a]
ys)
| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y = [a] -> [a] -> ([a], [a])
forall a. Eq a => [a] -> [a] -> ([a], [a])
dropCommonPrefix [a]
xs [a]
ys
dropCommonPrefix [a]
xs [a]
ys = ([a]
xs, [a]
ys)
dropExeExtension :: FilePath -> FilePath
dropExeExtension :: [Char] -> [Char]
dropExeExtension [Char]
filepath =
let exts :: [[Char]]
exts = [[Char]
ext | [Char]
ext <- [[Char]]
exeExtensions, [Char]
ext [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char]
""]
in [Char] -> Maybe [Char] -> [Char]
forall a. a -> Maybe a -> a
fromMaybe [Char]
filepath (Maybe [Char] -> [Char]) -> Maybe [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ do
ext <- ([Char] -> Bool) -> [[Char]] -> Maybe [Char]
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ([Char] -> [Char] -> Bool
`FilePath.isExtensionOf` [Char]
filepath) [[Char]]
exts
ext `FilePath.stripExtension` filepath
exeExtensions :: [String]
exeExtensions :: [[Char]]
exeExtensions = case (Arch
buildArch, OS
buildOS) of
(Arch
_, OS
Windows) -> [[Char]
"", [Char]
"exe"]
(Arch
_, OS
Ghcjs) -> [[Char]
"", [Char]
"exe"]
(Arch
Wasm32, OS
_) -> [[Char]
"", [Char]
"wasm"]
(Arch, OS)
_ -> [[Char]
""]
defaultPackageDescCwd :: Verbosity -> IO (RelativePath Pkg File)
defaultPackageDescCwd :: Verbosity -> IO (RelativePath Pkg 'File)
defaultPackageDescCwd Verbosity
verbosity = Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (RelativePath Pkg 'File)
tryFindPackageDesc Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
findPackageDesc
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> IO (Either CabalException (RelativePath Pkg File))
findPackageDesc :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (Either CabalException (RelativePath Pkg 'File))
findPackageDesc Maybe (SymbolicPath CWD ('Dir Pkg))
mbPkgDir =
do
let pkgDir :: [Char]
pkgDir = [Char]
-> (SymbolicPath CWD ('Dir Pkg) -> [Char])
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"." SymbolicPath CWD ('Dir Pkg) -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbPkgDir
files <- [Char] -> IO [[Char]]
getDirectoryContents [Char]
pkgDir
cabalFiles <-
filterM
(doesFileExist . uncurry (</>))
[ (pkgDir, file)
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == ".cabal"
]
case map snd cabalFiles of
[] -> Either CabalException (RelativePath Pkg 'File)
-> IO (Either CabalException (RelativePath Pkg 'File))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CabalException -> Either CabalException (RelativePath Pkg 'File)
forall a b. a -> Either a b
Left CabalException
NoDesc)
[[Char]
cabalFile] -> Either CabalException (RelativePath Pkg 'File)
-> IO (Either CabalException (RelativePath Pkg 'File))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RelativePath Pkg 'File
-> Either CabalException (RelativePath Pkg 'File)
forall a b. b -> Either a b
Right (RelativePath Pkg 'File
-> Either CabalException (RelativePath Pkg 'File))
-> RelativePath Pkg 'File
-> Either CabalException (RelativePath Pkg 'File)
forall a b. (a -> b) -> a -> b
$ [Char] -> RelativePath Pkg 'File
forall from (to :: FileOrDir).
HasCallStack =>
[Char] -> RelativePath from to
makeRelativePathEx [Char]
cabalFile)
[[Char]]
multiple -> Either CabalException (RelativePath Pkg 'File)
-> IO (Either CabalException (RelativePath Pkg 'File))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CabalException -> Either CabalException (RelativePath Pkg 'File)
forall a b. a -> Either a b
Left (CabalException -> Either CabalException (RelativePath Pkg 'File))
-> CabalException -> Either CabalException (RelativePath Pkg 'File)
forall a b. (a -> b) -> a -> b
$ [[Char]] -> CabalException
MultiDesc [[Char]]
multiple)
tryFindPackageDesc
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> IO (RelativePath Pkg File)
tryFindPackageDesc :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (RelativePath Pkg 'File)
tryFindPackageDesc Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
dir =
(CabalException -> IO (RelativePath Pkg 'File))
-> (RelativePath Pkg 'File -> IO (RelativePath Pkg 'File))
-> Either CabalException (RelativePath Pkg 'File)
-> IO (RelativePath Pkg 'File)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Verbosity -> CabalException -> IO (RelativePath Pkg 'File)
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity) RelativePath Pkg 'File -> IO (RelativePath Pkg 'File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CabalException (RelativePath Pkg 'File)
-> IO (RelativePath Pkg 'File))
-> IO (Either CabalException (RelativePath Pkg 'File))
-> IO (RelativePath Pkg 'File)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (Either CabalException (RelativePath Pkg 'File))
findPackageDesc Maybe (SymbolicPath CWD ('Dir Pkg))
dir
findHookedPackageDesc
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir Build)
-> IO (Maybe (SymbolicPath Pkg File))
findHookedPackageDesc :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
findHookedPackageDesc Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
dir = do
files <- [Char] -> IO [[Char]]
getDirectoryContents ([Char] -> IO [[Char]]) -> [Char] -> IO [[Char]]
forall a b. (a -> b) -> a -> b
$ Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> [Char]
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> [Char]
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
dir
buildInfoFiles <-
filterM
(doesFileExist . interpretSymbolicPath mbWorkDir)
[ dir </> makeRelativePathEx file
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == buildInfoExt
]
case buildInfoFiles of
[] -> Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
forall a. Maybe a
Nothing
[SymbolicPathX 'AllowAbsolute Pkg 'File
f] -> Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SymbolicPathX 'AllowAbsolute Pkg 'File
-> Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
forall a. a -> Maybe a
Just SymbolicPathX 'AllowAbsolute Pkg 'File
f)
[SymbolicPathX 'AllowAbsolute Pkg 'File]
_ -> Verbosity
-> CabalException
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)))
-> CabalException
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall a b. (a -> b) -> a -> b
$ [Char] -> CabalException
MultipleFilesWithExtension [Char]
buildInfoExt
buildInfoExt :: String
buildInfoExt :: [Char]
buildInfoExt = [Char]
".buildinfo"
stripCommonPrefix :: String -> String -> String
stripCommonPrefix :: [Char] -> [Char] -> [Char]
stripCommonPrefix (Char
x : [Char]
xs) (Char
y : [Char]
ys)
| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
y = [Char] -> [Char] -> [Char]
stripCommonPrefix [Char]
xs [Char]
ys
| Bool
otherwise = Char
y Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
ys
stripCommonPrefix [Char]
_ [Char]
ys = [Char]
ys