{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.Simple.Utils
( cabalVersion
, 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
, ordNubBy
, ordNubRight
, safeHead
, safeTail
, safeLast
, safeInit
, unintersperse
, wrapText
, wrapLine
, 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
, 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
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
dieNoVerbosity :: String -> IO a
dieNoVerbosity :: forall a. String -> IO a
dieNoVerbosity String
msg =
IOException -> IO a
forall a. HasCallStack => IOException -> IO a
ioError (String -> IOException
userError String
msg)
where
CallStack
_ = CallStack
HasCallStack => CallStack
callStack
ioeSetVerbatim :: IOError -> IOError
ioeSetVerbatim :: IOException -> IOException
ioeSetVerbatim IOException
e = IOException -> String -> IOException
ioeSetLocation IOException
e String
"dieVerbatim"
ioeGetVerbatim :: IOError -> Bool
ioeGetVerbatim :: IOException -> Bool
ioeGetVerbatim IOException
e = IOException -> String
ioeGetLocation IOException
e String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"dieVerbatim"
verbatimUserError :: String -> IOError
verbatimUserError :: String -> IOException
verbatimUserError = IOException -> IOException
ioeSetVerbatim (IOException -> IOException)
-> (String -> IOException) -> String -> IOException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IOException
userError
dieWithLocation' :: Verbosity -> FilePath -> Maybe Int -> String -> IO a
dieWithLocation' :: forall a. Verbosity -> String -> Maybe Int -> String -> IO a
dieWithLocation' Verbosity
verbosity String
filename Maybe Int
mb_lineno String
msg =
Verbosity -> String -> IO a
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity (String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$
String
filename
String -> String -> String
forall a. [a] -> [a] -> [a]
++ ( case Maybe Int
mb_lineno of
Just Int
lineno -> String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
lineno
Maybe Int
Nothing -> String
""
)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg
die' :: Verbosity -> String -> IO a
die' :: forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity String
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) -> (String -> IOException) -> String -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IOException
verbatimUserError
(String -> IO a) -> IO String -> IO a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> String -> IO String
annotateErrorString Verbosity
verbosity
(String -> IO String) -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO String
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> IO String) -> (String -> String) -> String -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> String -> String
wrapTextVerbosity Verbosity
verbosity
(String -> IO String) -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO String
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> IO String) -> (String -> String) -> String -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
addErrorPrefix
(String -> IO String) -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO String
prefixWithProgName String
msg
data VerboseException a = VerboseException CallStack POSIXTime Verbosity a
deriving (Int -> VerboseException a -> String -> String
[VerboseException a] -> String -> String
VerboseException a -> String
(Int -> VerboseException a -> String -> String)
-> (VerboseException a -> String)
-> ([VerboseException a] -> String -> String)
-> Show (VerboseException a)
forall a. Show a => Int -> VerboseException a -> String -> String
forall a. Show a => [VerboseException a] -> String -> String
forall a. Show a => VerboseException a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: forall a. Show a => Int -> VerboseException a -> String -> String
showsPrec :: Int -> VerboseException a -> String -> String
$cshow :: forall a. Show a => VerboseException a -> String
show :: VerboseException a -> String
$cshowList :: forall a. Show a => [VerboseException a] -> String -> String
showList :: [VerboseException a] -> String -> String
Show, Typeable)
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 POSIXTime
getPOSIXTime
throwIO $ VerboseException callStack ts verbosity exception
instance Exception (VerboseException CabalException) where
displayException :: VerboseException CabalException -> [Char]
displayException :: VerboseException CabalException -> String
displayException (VerboseException CallStack
stack POSIXTime
timestamp Verbosity
verb CabalException
cabalexception) =
Verbosity -> String -> String
withOutputMarker
Verbosity
verb
( [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"Error: [Cabal-"
, Int -> String
forall a. Show a => a -> String
show (CabalException -> Int
exceptionCode CabalException
cabalexception)
, String
"]\n"
]
)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ CallStack -> POSIXTime -> Verbosity -> String -> String
exceptionWithMetadata CallStack
stack POSIXTime
timestamp Verbosity
verb (CabalException -> String
exceptionMessage CabalException
cabalexception)
dieNoWrap :: Verbosity -> String -> IO a
dieNoWrap :: forall a. Verbosity -> String -> IO a
dieNoWrap Verbosity
verbosity String
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) -> (String -> IOException) -> String -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IOException
verbatimUserError
(String -> IO a) -> IO String -> IO a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> String -> IO String
annotateErrorString
Verbosity
verbosity
(String -> String
addErrorPrefix String
msg)
addErrorPrefix :: String -> String
addErrorPrefix :: String -> String
addErrorPrefix String
msg
| String
errorPrefix String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
msg = String
msg
| Bool
otherwise = [String] -> String
unwords [String
errorPrefix, String
msg]
errorPrefix :: String
errorPrefix :: String
errorPrefix = String
"Error:"
prefixWithProgName :: String -> IO String
prefixWithProgName :: String -> IO String
prefixWithProgName String
msg = do
pname <- IO String
getProgName
return $ pname ++ ": " ++ msg
annotateErrorString :: Verbosity -> String -> IO String
annotateErrorString :: Verbosity -> String -> IO String
annotateErrorString Verbosity
verbosity String
msg = do
ts <- IO POSIXTime
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 POSIXTime
getPOSIXTime
flip modifyIOError act $
ioeModifyErrorString $
withMetadata ts NeverMark VerboseTrace verbosity
ioeModifyErrorString :: (String -> String) -> IOError -> IOError
ioeModifyErrorString :: (String -> String) -> IOException -> IOException
ioeModifyErrorString = ASetter IOException IOException String String
-> (String -> String) -> IOException -> IOException
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter IOException IOException String String
Lens' IOException String
ioeErrorString
ioeErrorString :: Lens' IOError String
ioeErrorString :: Lens' IOException String
ioeErrorString String -> f String
f IOException
ioe = IOException -> String -> IOException
ioeSetErrorString IOException
ioe (String -> IOException) -> f String -> f IOException
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> f String
f (IOException -> String
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 String
getProgName
hPutStr stderr (message pname se)
cont se
message :: String -> Exception.SomeException -> String
message :: String -> SomeException -> String
message String
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 -> String
ioeGetErrorString IOException
ioe String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
| IOException -> Bool
isUserError IOException
ioe ->
let file :: String
file = case IOException -> Maybe String
ioeGetFileName IOException
ioe of
Maybe String
Nothing -> String
""
Just String
path -> String
path String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
location String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
location :: String
location = case IOException -> String
ioeGetLocation IOException
ioe of
l :: String
l@(Char
n : String
_) | Char -> Bool
isDigit Char
n -> Char
':' Char -> String -> String
forall a. a -> [a] -> [a]
: String
l
String
_ -> String
""
detail :: String
detail = IOException -> String
ioeGetErrorString IOException
ioe
in String -> String
wrapText (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
addErrorPrefix (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
pname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
detail
Maybe IOException
_ ->
e -> String
forall e. Exception e => e -> String
displaySomeException e
se String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
displaySomeException :: Exception.Exception e => e -> String
displaySomeException :: forall e. Exception e => e -> String
displaySomeException e
se = e -> String
forall e. Exception e => e -> String
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 -> String -> IO ()
warn Verbosity
verbosity String
msg = String -> Verbosity -> String -> IO ()
warnMessage String
"Warning" Verbosity
verbosity String
msg
warnError :: Verbosity -> String -> IO ()
warnError :: Verbosity -> String -> IO ()
warnError Verbosity
verbosity String
message = String -> Verbosity -> String -> IO ()
warnMessage String
"Error" Verbosity
verbosity String
message
warnMessage :: String -> Verbosity -> String -> IO ()
warnMessage :: String -> Verbosity -> String -> IO ()
warnMessage String
l Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hFlush stdout
hPutStr stderr
. withMetadata ts NormalMark FlagTrace verbosity
. wrapTextVerbosity verbosity
$ l ++ ": " ++ msg
notice :: Verbosity -> String -> IO ()
notice :: Verbosity -> String -> IO ()
notice Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NormalMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
noticeNoWrap :: Verbosity -> String -> IO ()
noticeNoWrap :: Verbosity -> String -> IO ()
noticeNoWrap Verbosity
verbosity String
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 POSIXTime
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NormalMark FlagTrace verbosity $
Disp.renderStyle defaultStyle $
msg
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage Verbosity
verbosity String
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 -> String -> IO ()
noticeNoWrap Verbosity
verbosity (String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
' ' Char -> String -> String
forall a. a -> [a] -> [a]
: PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow PackageIdentifier
pkgid String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"...")
info :: Verbosity -> String -> IO ()
info :: Verbosity -> String -> IO ()
info Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
infoNoWrap :: Verbosity -> String -> IO ()
infoNoWrap :: Verbosity -> String -> IO ()
infoNoWrap Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
msg
debug :: Verbosity -> String -> IO ()
debug :: Verbosity -> String -> IO ()
debug Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
wrapTextVerbosity verbosity $
msg
hFlush stdout
debugNoWrap :: Verbosity -> String -> IO ()
debugNoWrap :: Verbosity -> String -> IO ()
debugNoWrap Verbosity
verbosity String
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 POSIXTime
getPOSIXTime
hPutStr h $
withMetadata ts NeverMark FlagTrace verbosity $
msg
hFlush stdout
chattyTry
:: String
-> IO ()
-> IO ()
chattyTry :: String -> IO () -> IO ()
chattyTry String
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 -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Error while " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desc String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ IOException -> String
forall a. Show a => a -> String
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 -> String -> String
wrapTextVerbosity Verbosity
verb
| Verbosity -> Bool
isVerboseNoWrap Verbosity
verb = String -> String
withTrailingNewline
| Bool
otherwise = String -> String
withTrailingNewline (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
wrapText
withTimestamp :: Verbosity -> POSIXTime -> String -> String
withTimestamp :: Verbosity -> POSIXTime -> String -> String
withTimestamp Verbosity
v POSIXTime
ts String
msg
| Verbosity -> Bool
isVerboseTimestamp Verbosity
v = String
msg'
| Bool
otherwise = String
msg
where
msg' :: String
msg' = case String -> [String]
lines String
msg of
[] -> String -> String
tsstr String
"\n"
String
l1 : [String]
rest -> [String] -> String
unlines (String -> String
tsstr (Char
' ' Char -> String -> String
forall a. a -> [a] -> [a]
: String
l1) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
contpfx String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
rest)
tsstr :: String -> String
tsstr = Maybe Int -> Double -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
3) (POSIXTime -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac POSIXTime
ts :: Double)
contpfx :: String
contpfx = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> String
tsstr String
" ")) Char
' '
withOutputMarker :: Verbosity -> String -> String
withOutputMarker :: Verbosity -> String -> String
withOutputMarker Verbosity
v String
xs | Bool -> Bool
not (Verbosity -> Bool
isVerboseMarkOutput Verbosity
v) = String
xs
withOutputMarker Verbosity
_ String
"" = String
""
withOutputMarker Verbosity
_ String
xs =
String
"-----BEGIN CABAL OUTPUT-----\n"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
withTrailingNewline String
xs
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-----END CABAL OUTPUT-----\n"
withTrailingNewline :: String -> String
withTrailingNewline :: String -> String
withTrailingNewline String
"" = String
""
withTrailingNewline (Char
x : String
xs) = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: Char -> String -> String
go Char
x String
xs
where
go :: Char -> String -> String
go Char
_ (Char
c : String
cs) = Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: Char -> String -> String
go Char
c String
cs
go Char
'\n' String
"" = String
""
go Char
_ String
"" = String
"\n"
withCallStackPrefix :: WithCallStack (TraceWhen -> Verbosity -> String -> String)
withCallStackPrefix :: WithCallStack (TraceWhen -> Verbosity -> String -> String)
withCallStackPrefix TraceWhen
tracer Verbosity
verbosity String
s =
(HasCallStack => String) -> String
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => String) -> String)
-> (HasCallStack => String) -> String
forall a b. (a -> b) -> a -> b
$
( if Verbosity -> Bool
isVerboseCallSite Verbosity
verbosity
then
String
HasCallStack => String
parentSrcLocPrefix
String -> String -> String
forall a. [a] -> [a] -> [a]
++
if Verbosity -> Bool
isVerboseMarkOutput Verbosity
verbosity
then String
"\n"
else String
""
else String
""
)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ ( case Verbosity -> TraceWhen -> Maybe String
traceWhen Verbosity
verbosity TraceWhen
tracer of
Just String
pre -> String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++ CallStack -> String
prettyCallStack CallStack
HasCallStack => CallStack
callStack String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
Maybe String
Nothing -> String
""
)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
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 String
traceWhen Verbosity
_ TraceWhen
AlwaysTrace = String -> Maybe String
forall a. a -> Maybe a
Just String
""
traceWhen Verbosity
v TraceWhen
VerboseTrace | Verbosity
v Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose = String -> Maybe String
forall a. a -> Maybe a
Just String
""
traceWhen Verbosity
v TraceWhen
FlagTrace | Verbosity -> Bool
isVerboseCallStack Verbosity
v = String -> Maybe String
forall a. a -> Maybe a
Just String
"----\n"
traceWhen Verbosity
_ TraceWhen
_ = Maybe String
forall a. Maybe a
Nothing
data MarkWhen = AlwaysMark | NormalMark | NeverMark
withMetadata :: WithCallStack (POSIXTime -> MarkWhen -> TraceWhen -> Verbosity -> String -> String)
withMetadata :: WithCallStack
(POSIXTime
-> MarkWhen -> TraceWhen -> Verbosity -> String -> String)
withMetadata POSIXTime
ts MarkWhen
marker TraceWhen
tracer Verbosity
verbosity String
x =
(HasCallStack => String) -> String
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
((HasCallStack => String) -> String)
-> (HasCallStack => String) -> String
forall a b. (a -> b) -> a -> b
$
String -> String
withTrailingNewline
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithCallStack (TraceWhen -> Verbosity -> String -> String)
TraceWhen -> Verbosity -> String -> String
withCallStackPrefix TraceWhen
tracer Verbosity
verbosity
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ( case MarkWhen
marker of
MarkWhen
AlwaysMark -> Verbosity -> String -> String
withOutputMarker Verbosity
verbosity
MarkWhen
NormalMark
| Bool -> Bool
not (Verbosity -> Bool
isVerboseQuiet Verbosity
verbosity) ->
Verbosity -> String -> String
withOutputMarker Verbosity
verbosity
| Bool
otherwise ->
String -> String
forall a. a -> a
id
MarkWhen
NeverMark -> String -> String
forall a. a -> a
id
)
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
clearMarkers
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> POSIXTime -> String -> String
withTimestamp Verbosity
verbosity POSIXTime
ts
(String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
x
exceptionWithMetadata :: CallStack -> POSIXTime -> Verbosity -> String -> String
exceptionWithMetadata :: CallStack -> POSIXTime -> Verbosity -> String -> String
exceptionWithMetadata CallStack
stack POSIXTime
ts Verbosity
verbosity String
x =
String -> String
withTrailingNewline
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallStack -> Verbosity -> String -> String
exceptionWithCallStackPrefix CallStack
stack Verbosity
verbosity
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> String -> String
withOutputMarker Verbosity
verbosity
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
clearMarkers
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> POSIXTime -> String -> String
withTimestamp Verbosity
verbosity POSIXTime
ts
(String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
x
clearMarkers :: String -> String
clearMarkers :: String -> String
clearMarkers String
s = [String] -> String
unlines ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
isMarker ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
where
isMarker :: String -> Bool
isMarker String
"-----BEGIN CABAL OUTPUT-----" = Bool
False
isMarker String
"-----END CABAL OUTPUT-----" = Bool
False
isMarker String
_ = Bool
True
exceptionWithCallStackPrefix :: CallStack -> Verbosity -> String -> String
exceptionWithCallStackPrefix :: CallStack -> Verbosity -> String -> String
exceptionWithCallStackPrefix CallStack
stack Verbosity
verbosity String
s =
String
s
String -> String -> String
forall a. [a] -> [a] -> [a]
++ (HasCallStack => String) -> String
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
( ( if Verbosity -> Bool
isVerboseCallSite Verbosity
verbosity
then
String
HasCallStack => String
parentSrcLocPrefix
String -> String -> String
forall a. [a] -> [a] -> [a]
++
if Verbosity -> Bool
isVerboseMarkOutput Verbosity
verbosity
then String
"\n"
else String
""
else String
""
)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ ( if Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
verbose
then CallStack -> String
prettyCallStack CallStack
stack String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
else String
""
)
)
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 -> String -> IO ()
infoNoWrap Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"Running: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> case CreateProcess -> CmdSpec
Process.cmdspec CreateProcess
cp of
Process.ShellCommand String
sh -> String
sh
Process.RawCommand String
path [String]
args -> String -> [String] -> String
Process.showCommandForUser String
path [String]
args
case CreateProcess -> Maybe [(String, String)]
Process.env CreateProcess
cp of
Just [(String, String)]
env -> Verbosity -> String -> IO ()
debugNoWrap Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"with environment: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, String)] -> String
forall a. Show a => a -> String
show [(String, String)]
env
Maybe [(String, String)]
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
case CreateProcess -> Maybe String
Process.cwd CreateProcess
cp of
Just String
cwd -> Verbosity -> String -> IO ()
debugNoWrap Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"with working directory: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
cwd
Maybe String
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))
-> String
-> [String]
-> IO ()
rawSystemExit Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir String
path [String]
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))
-> String
-> [String]
-> Maybe [(String, String)]
-> IO ExitCode
rawSystemExitCode Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir String
path [String]
args Maybe [(String, String)]
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))
-> String
-> [String]
-> Maybe [(String, String)]
-> IO ExitCode
rawSystemExitCode Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir String
path [String]
args Maybe [(String, String)]
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
$
(String -> [String] -> CreateProcess
proc String
path [String]
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 String
sh -> String
sh
Process.RawCommand String
path [String]
_args -> String
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 (String -> Handle
forall a. HasCallStack => String -> a
error String
"fromCreatePipe: Nothing") Handle -> Handle
forall a. a -> a
id
rawSystemExitWithEnv
:: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnv :: Verbosity -> String -> [String] -> [(String, String)] -> IO ()
rawSystemExitWithEnv Verbosity
verbosity =
Verbosity
-> Maybe (SymbolicPath CWD (ZonkAny 7))
-> String
-> [String]
-> [(String, String)]
-> IO ()
forall (to :: FileOrDir).
Verbosity
-> Maybe (SymbolicPath CWD to)
-> String
-> [String]
-> [(String, String)]
-> 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)
-> String
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnvCwd Verbosity
verbosity Maybe (SymbolicPath CWD to)
mbWorkDir String
path [String]
args [(String, String)]
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
$
(String -> [String] -> CreateProcess
proc String
path [String]
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
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ExitCode
rawSystemIOWithEnv Verbosity
verbosity String
path [String]
args Maybe String
mcwd Maybe [(String, String)]
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
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO ()
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, ())
forall a.
Verbosity
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO a
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, a)
rawSystemIOWithEnvAndAction
Verbosity
verbosity
String
path
[String]
args
Maybe String
mcwd
Maybe [(String, String)]
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
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO a
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (ExitCode, a)
rawSystemIOWithEnvAndAction Verbosity
verbosity String
path [String]
args Maybe String
mcwd Maybe [(String, String)]
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 =
(String -> [String] -> CreateProcess
proc String
path [String]
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 -> String -> [String] -> IO mode
rawSystemStdout Verbosity
verbosity String
path [String]
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
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, String, ExitCode)
forall mode.
KnownIODataMode mode =>
Verbosity
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, String, ExitCode)
rawSystemStdInOut
Verbosity
verbosity
String
path
[String]
args
Maybe String
forall a. Maybe a
Nothing
Maybe [(String, String)]
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
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> Maybe IOData
-> IODataMode mode
-> IO (mode, String, ExitCode)
rawSystemStdInOut Verbosity
verbosity String
path [String]
args Maybe String
mcwd Maybe [(String, String)]
menv Maybe IOData
input IODataMode mode
_ = (HasCallStack => IO (mode, String, ExitCode))
-> IO (mode, String, ExitCode)
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => IO (mode, String, ExitCode))
-> IO (mode, String, ExitCode))
-> (HasCallStack => IO (mode, String, ExitCode))
-> IO (mode, String, ExitCode)
forall a b. (a -> b) -> a -> b
$ do
let cp :: CreateProcess
cp =
(String -> [String] -> CreateProcess
proc String
path [String]
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 String))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException String))
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 String))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException String)))
-> (Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO (Either SomeException mode, Either SomeException String))
-> IO
(ExitCode,
(Either SomeException mode, Either SomeException String))
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 String)
-> IO ()
-> IO (Either SomeException mode, Either SomeException String))
-> IO ()
-> IO (Either SomeException mode, Either SomeException String)
-> IO (Either SomeException mode, Either SomeException String)
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Either SomeException mode, Either SomeException String)
-> IO ()
-> IO (Either SomeException mode, Either SomeException String)
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 String)
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String)
-> IO (Either SomeException mode, Either SomeException String)
forall a b. (a -> b) -> a -> b
$ do
Handle -> Bool -> IO ()
hSetBinaryMode Handle
errh Bool
False
IO String
-> (AsyncM String
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String)
forall a b. NFData a => IO a -> (AsyncM a -> IO b) -> IO b
withAsyncNF (Handle -> IO String
hGetContents Handle
errh) ((AsyncM String
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String))
-> (AsyncM String
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String)
forall a b. (a -> b) -> a -> b
$ \AsyncM String
errA -> IO mode
-> (AsyncM mode
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String)
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 String))
-> IO (Either SomeException mode, Either SomeException String))
-> (AsyncM mode
-> IO (Either SomeException mode, Either SomeException String))
-> IO (Either SomeException mode, Either SomeException String)
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 -> String
""
Just IOData
d | IOData -> Bool
IOData.null IOData
d -> String
""
Just (IODataText String
inp) -> String
"\nstdin input:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
inp
Just (IODataBinary ByteString
inp) -> String
"\nstdin input (binary):\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
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 -> String -> IOException
ioeSetFileName IOException
ioe (String
"output of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
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 :: String
-> (String -> String) -> Verbosity -> String -> IO (Maybe Version)
findProgramVersion String
versionArg String -> String
selectVersion Verbosity
verbosity String
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 -> String -> [String] -> IO String
forall mode.
KnownIODataMode mode =>
Verbosity -> String -> [String] -> IO mode
rawSystemStdout Verbosity
verbosity String
path [String
versionArg]
IO String -> (IOException -> IO String) -> IO String
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` (\IOException
_ -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"")
IO String
-> (VerboseException CabalException -> IO String) -> IO String
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(VerboseException CabalException
_ :: VerboseException CabalException) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"")
IO String -> (ExitCode -> IO String) -> IO String
forall a. IO a -> (ExitCode -> IO a) -> IO a
`catchExit` (\ExitCode
_ -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"")
let version :: Maybe Version
version = String -> Maybe Version
forall a. Parsec a => String -> Maybe a
simpleParsec (String -> String
selectVersion String
str)
case version of
Maybe Version
Nothing ->
Verbosity -> String -> IO ()
warn Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"cannot determine version of "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" :\n"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
str
Just Version
v -> Verbosity -> String -> IO ()
debug Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
path String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is version " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
v
return version
xargs
:: Int
-> ([String] -> IO ())
-> [String]
-> [String]
-> IO ()
xargs :: Int -> ([String] -> IO ()) -> [String] -> [String] -> IO ()
xargs Int
maxSize [String] -> IO ()
rawSystemFun [String]
fixedArgs [String]
bigArgs =
let fixedArgSize :: Int
fixedArgSize = [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
fixedArgs) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [String] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
fixedArgs
chunkSize :: Int
chunkSize = Int
maxSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
fixedArgSize
in ([String] -> IO ()) -> [[String]] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ ([String] -> IO ()
rawSystemFun ([String] -> IO ()) -> ([String] -> [String]) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String]
fixedArgs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++)) (Int -> [String] -> [[String]]
forall {t :: * -> *} {a}. Foldable t => Int -> [t a] -> [[t a]]
chunks Int
chunkSize [String]
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 RelativePath searchDir 'File
fileName =
(SymbolicPathX allowAbsolute Pkg 'File -> String)
-> [SymbolicPathX allowAbsolute Pkg 'File]
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
forall a. (a -> String) -> [a] -> IO (Maybe a)
findFirstFile
(Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir)
[ SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath 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
$ String -> CabalException
FindFile (String -> CabalException) -> String -> CabalException
forall a b. (a -> b) -> a -> b
$ RelativePath searchDir 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath RelativePath 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 RelativePath searchDir 'File
basename =
(SymbolicPathX allowAbsolute Pkg 'File -> String)
-> [SymbolicPathX allowAbsolute Pkg 'File]
-> IO [SymbolicPathX allowAbsolute Pkg 'File]
forall a. (a -> String) -> [a] -> IO [a]
findAllFiles
(Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir)
[ SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath searchDir 'File
basename RelativePath searchDir 'File
-> String -> RelativePath searchDir 'File
forall p. FileLike p => p -> String -> p
<.> String
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 String
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 RelativePath searchDir 'File
baseName =
((SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> String)
-> [(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
forall a. (a -> String) -> [a] -> IO (Maybe a)
findFirstFile
((SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File -> String)
-> (SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)
-> String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File -> String
mkPath)
[ (SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
path, RelativePath searchDir 'File
baseName RelativePath searchDir 'File
-> String -> RelativePath searchDir 'File
forall p. FileLike p => p -> String -> p
<.> String
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 String
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)
-> RelativePath searchDir 'File -> String
mkPath SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
base RelativePath searchDir 'File
file =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg 'File -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
cwd (SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
base SymbolicPathX allowAbsolute Pkg ('Dir searchDir)
-> RelativePath searchDir 'File
-> SymbolicPathX allowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath searchDir 'File
file)
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile :: forall a. (a -> String) -> [a] -> IO (Maybe a)
findFirstFile a -> String
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 <- String -> IO Bool
doesFileExist (a -> String
file a
x)
if exists
then return (Just x)
else findFirst xs
findAllFiles :: (a -> FilePath) -> [a] -> IO [a]
findAllFiles :: forall a. (a -> String) -> [a] -> IO [a]
findAllFiles a -> String
file = (a -> IO Bool) -> [a] -> IO [a]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
doesFileExist (String -> IO Bool) -> (a -> String) -> a -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
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
(String -> RelativePath searchDir 'File
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx (String -> RelativePath searchDir 'File)
-> String -> RelativePath searchDir 'File
forall a b. (a -> b) -> a -> b
$ ModuleName -> String
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] -> [String] -> CabalException
FindModuleFileEx ModuleName
mod_name [Suffix]
extensions ((SymbolicPathX allowAbsolute Pkg ('Dir searchDir) -> String)
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX allowAbsolute Pkg ('Dir searchDir) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
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 :: String -> IO [String]
getDirectoryContentsRecursive String
topdir = [String] -> IO [String]
recurseDirectories [String
""]
where
recurseDirectories :: [FilePath] -> IO [FilePath]
recurseDirectories :: [String] -> IO [String]
recurseDirectories [] = [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
recurseDirectories (String
dir : [String]
dirs) = IO [String] -> IO [String]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [String] -> IO [String]) -> IO [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ do
(files, dirs') <- [String] -> [String] -> [String] -> IO ([String], [String])
collect [] [] ([String] -> IO ([String], [String]))
-> IO [String] -> IO ([String], [String])
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
getDirectoryContents (String
topdir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
dir)
files' <- recurseDirectories (dirs' ++ dirs)
return (files ++ files')
where
collect :: [String] -> [String] -> [String] -> IO ([String], [String])
collect [String]
files [String]
dirs' [] =
([String], [String]) -> IO ([String], [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
( [String] -> [String]
forall a. [a] -> [a]
reverse [String]
files
, [String] -> [String]
forall a. [a] -> [a]
reverse [String]
dirs'
)
collect [String]
files [String]
dirs' (String
entry : [String]
entries)
| String -> Bool
ignore String
entry =
[String] -> [String] -> [String] -> IO ([String], [String])
collect [String]
files [String]
dirs' [String]
entries
collect [String]
files [String]
dirs' (String
entry : [String]
entries) = do
let dirEntry :: String
dirEntry = String
dir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
entry
isDirectory <- String -> IO Bool
doesDirectoryExist (String
topdir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
dirEntry)
if isDirectory
then collect files (dirEntry : dirs') entries
else collect (dirEntry : files) dirs' entries
ignore :: String -> Bool
ignore [Char
'.'] = Bool
True
ignore [Char
'.', Char
'.'] = Bool
True
ignore String
_ = Bool
False
isInSearchPath :: FilePath -> IO Bool
isInSearchPath :: String -> IO Bool
isInSearchPath String
path = ([String] -> Bool) -> IO [String] -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem String
path) IO [String]
getSearchPath
addLibraryPath
:: OS
-> [FilePath]
-> [(String, String)]
-> [(String, String)]
addLibraryPath :: OS -> [String] -> [(String, String)] -> [(String, String)]
addLibraryPath OS
os [String]
paths = [(String, String)] -> [(String, String)]
addEnv
where
pathsString :: String
pathsString = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate [Char
searchPathSeparator] [String]
paths
ldPath :: String
ldPath = case OS
os of
OS
OSX -> String
"DYLD_LIBRARY_PATH"
OS
_ -> String
"LD_LIBRARY_PATH"
addEnv :: [(String, String)] -> [(String, String)]
addEnv [] = [(String
ldPath, String
pathsString)]
addEnv ((String
key, String
value) : [(String, String)]
xs)
| String
key String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
ldPath =
if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
value
then (String
key, String
pathsString) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
: [(String, String)]
xs
else (String
key, String
value String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Char
searchPathSeparator Char -> String -> String
forall a. a -> [a] -> [a]
: String
pathsString)) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
: [(String, String)]
xs
| Bool
otherwise = (String
key, String
value) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
: [(String, String)] -> [(String, String)]
addEnv [(String, String)]
xs
moreRecentFile :: FilePath -> FilePath -> IO Bool
moreRecentFile :: String -> String -> IO Bool
moreRecentFile String
a String
b = do
exists <- String -> IO Bool
doesFileExist String
b
if not exists
then return True
else do
tb <- getModificationTime b
ta <- getModificationTime a
return (ta > tb)
existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool
existsAndIsMoreRecentThan :: String -> String -> IO Bool
existsAndIsMoreRecentThan String
a String
b = do
exists <- String -> IO Bool
doesFileExist String
a
if not exists
then return False
else a `moreRecentFile` b
createDirectoryIfMissingVerbose
:: Verbosity
-> Bool
-> FilePath
-> IO ()
createDirectoryIfMissingVerbose :: Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
create_parents String
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
$ [String] -> IO ()
createDirs (String -> [String]
parents String
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
$ [String] -> IO ()
createDirs (Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 (String -> [String]
parents String
path0))
where
parents :: String -> [String]
parents = [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> String) -> [String] -> [String]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
(</>) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitDirectories (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
normalise
createDirs :: [String] -> IO ()
createDirs [] = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
createDirs (String
dir : []) = String -> (IOException -> IO ()) -> IO ()
createDir String
dir IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO
createDirs (String
dir : [String]
dirs) =
String -> (IOException -> IO ()) -> IO ()
createDir String
dir ((IOException -> IO ()) -> IO ())
-> (IOException -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IOException
_ -> do
[String] -> IO ()
createDirs [String]
dirs
String -> (IOException -> IO ()) -> IO ()
createDir String
dir IOException -> IO ()
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO
createDir :: FilePath -> (IOException -> IO ()) -> IO ()
createDir :: String -> (IOException -> IO ()) -> IO ()
createDir String
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 -> String -> IO ()
createDirectoryVerbose Verbosity
verbosity String
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 <- String -> IO Bool
doesDirectoryExist String
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 -> String -> IO ()
createDirectoryVerbose Verbosity
verbosity String
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 -> String -> IO ()
info Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"creating " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dir
String -> IO ()
createDirectory String
dir
String -> IO ()
setDirOrdinary String
dir
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose :: Verbosity -> String -> String -> IO ()
copyFileVerbose Verbosity
verbosity String
src String
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 -> String -> IO ()
info Verbosity
verbosity (String
"copy " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
src String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dest)
String -> String -> IO ()
copyFile String
src String
dest
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile :: Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity String
src String
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 -> String -> IO ()
info Verbosity
verbosity (String
"Installing " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
src String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dest)
String -> String -> IO ()
copyOrdinaryFile String
src String
dest
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile :: Verbosity -> String -> String -> IO ()
installExecutableFile Verbosity
verbosity String
src String
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 -> String -> IO ()
info Verbosity
verbosity (String
"Installing executable " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
src String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dest)
String -> String -> IO ()
copyExecutableFile String
src String
dest
installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installMaybeExecutableFile :: Verbosity -> String -> String -> IO ()
installMaybeExecutableFile Verbosity
verbosity String
src String
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 <- String -> IO Permissions
getPermissions String
src
if (executable perms)
then installExecutableFile verbosity src dest
else installOrdinaryFile verbosity src dest
copyFileTo
:: Verbosity
-> FilePath
-> FilePath
-> IO ()
copyFileTo :: Verbosity -> String -> String -> IO ()
copyFileTo Verbosity
verbosity String
dir String
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
(String -> SymbolicPath Pkg ('Dir (ZonkAny 6))
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
dir)
(String -> RelativePath Pkg 'File
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx String
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 :: String
targetFile = SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> String
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> String
i (SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> String)
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 5) -> String
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 -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True (String -> String
takeDirectory String
targetFile)
Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity (RelativePath Pkg 'File -> String
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> String
i RelativePath Pkg 'File
file) String
targetFile
where
i :: SymbolicPathX allowAbs Pkg to -> FilePath
i :: forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> String
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbs Pkg to -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
copyFilesWith
:: (Verbosity -> FilePath -> FilePath -> IO ())
-> Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
copyFilesWith :: (Verbosity -> String -> String -> IO ())
-> Verbosity -> String -> [(String, String)] -> IO ()
copyFilesWith Verbosity -> String -> String -> IO ()
doCopy Verbosity
verbosity String
targetDir [(String, String)]
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 :: [String]
dirs = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
targetDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</>) ([String] -> [String])
-> ([(String, String)] -> [String])
-> [(String, String)]
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. Ord a => [a] -> [a]
ordNub ([String] -> [String])
-> ([(String, String)] -> [String])
-> [(String, String)]
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, String) -> String) -> [(String, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String
takeDirectory (String -> String)
-> ((String, String) -> String) -> (String, String) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, String) -> String
forall a b. (a, b) -> b
snd) ([(String, String)] -> [String]) -> [(String, String)] -> [String]
forall a b. (a -> b) -> a -> b
$ [(String, String)]
srcFiles
(String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True) [String]
dirs
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ let src :: String
src = String
srcBase String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
srcFile
dest :: String
dest = String
targetDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
srcFile
in Verbosity -> String -> String -> IO ()
doCopy Verbosity
verbosity String
src String
dest
| (String
srcBase, String
srcFile) <- [(String, String)]
srcFiles
]
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles :: Verbosity -> String -> [(String, String)] -> IO ()
copyFiles Verbosity
v String
fp [(String, String)]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> String -> String -> IO ())
-> Verbosity -> String -> [(String, String)] -> IO ()
copyFilesWith Verbosity -> String -> String -> IO ()
copyFileVerbose Verbosity
v String
fp [(String, String)]
fs)
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles :: Verbosity -> String -> [(String, String)] -> IO ()
installOrdinaryFiles Verbosity
v String
fp [(String, String)]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> String -> String -> IO ())
-> Verbosity -> String -> [(String, String)] -> IO ()
copyFilesWith Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
v String
fp [(String, String)]
fs)
installExecutableFiles
:: Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
installExecutableFiles :: Verbosity -> String -> [(String, String)] -> IO ()
installExecutableFiles Verbosity
v String
fp [(String, String)]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> String -> String -> IO ())
-> Verbosity -> String -> [(String, String)] -> IO ()
copyFilesWith Verbosity -> String -> String -> IO ()
installExecutableFile Verbosity
v String
fp [(String, String)]
fs)
installMaybeExecutableFiles
:: Verbosity
-> FilePath
-> [(FilePath, FilePath)]
-> IO ()
installMaybeExecutableFiles :: Verbosity -> String -> [(String, String)] -> IO ()
installMaybeExecutableFiles Verbosity
v String
fp [(String, String)]
fs = (HasCallStack => IO ()) -> IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((Verbosity -> String -> String -> IO ())
-> Verbosity -> String -> [(String, String)] -> IO ()
copyFilesWith Verbosity -> String -> String -> IO ()
installMaybeExecutableFile Verbosity
v String
fp [(String, String)]
fs)
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents :: Verbosity -> String -> String -> IO ()
installDirectoryContents Verbosity
verbosity String
srcDir String
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 -> String -> IO ()
info Verbosity
verbosity (String
"copy directory '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
srcDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' to '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
destDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'.")
srcFiles <- String -> IO [String]
getDirectoryContentsRecursive String
srcDir
installOrdinaryFiles verbosity destDir [(srcDir, f) | f <- srcFiles]
copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursive :: Verbosity -> String -> String -> IO ()
copyDirectoryRecursive Verbosity
verbosity String
srcDir String
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 -> String -> IO ()
info Verbosity
verbosity (String
"copy directory '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
srcDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' to '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
destDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'.")
srcFiles <- String -> IO [String]
getDirectoryContentsRecursive String
srcDir
copyFilesWith
(const copyFile)
verbosity
destDir
[ (srcDir, f)
| f <- srcFiles
]
doesExecutableExist :: FilePath -> IO Bool
doesExecutableExist :: String -> IO Bool
doesExecutableExist String
f = do
exists <- String -> IO Bool
doesFileExist String
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
:: FilePath
-> String
-> (FilePath -> Handle -> IO a)
-> IO a
withTempFile :: forall a. String -> String -> (String -> Handle -> IO a) -> IO a
withTempFile String
tmpDir String
template String -> 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
$
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir (ZonkAny 0))
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall tmpDir a.
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileCwd Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (String -> SymbolicPath Pkg ('Dir (ZonkAny 0))
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
tmpDir) String
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 -> String -> Handle -> IO a
f (SymbolicPathX 'AllowAbsolute Pkg 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath SymbolicPathX 'AllowAbsolute Pkg 'File
fp) Handle
h
withTempFileCwd
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir tmpDir)
-> String
-> (SymbolicPath Pkg File -> Handle -> IO a)
-> IO a
withTempFileCwd :: forall tmpDir a.
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileCwd = (HasCallStack =>
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack =>
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> (HasCallStack =>
Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a)
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a b. (a -> b) -> a -> b
$ TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
forall a tmpDir.
TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileEx TempFileOptions
defaultTempFileOptions
withTempFileEx
:: forall a tmpDir
. TempFileOptions
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir tmpDir)
-> String
-> (SymbolicPath Pkg File -> Handle -> IO a)
-> IO a
withTempFileEx :: forall a tmpDir.
TempFileOptions
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir)
-> String
-> (SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a)
-> IO a
withTempFileEx TempFileOptions
opts Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir tmpDir)
tmpDir String
template SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a
action =
(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 (String, Handle)
-> ((String, Handle) -> IO ())
-> ((String, Handle) -> IO a)
-> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket
(String -> String -> IO (String, Handle)
openTempFile (SymbolicPath Pkg ('Dir tmpDir) -> String
i SymbolicPath Pkg ('Dir tmpDir)
tmpDir) String
template)
( \(String
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
$
String -> IO ()
removeFile (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
name
)
(((String, Handle) -> HasCallStack => IO a)
-> WithCallStack ((String, Handle) -> IO a)
forall a b.
(a -> WithCallStack (IO b)) -> WithCallStack (a -> IO b)
withLexicalCallStack (\(String
fn, Handle
h) -> SymbolicPathX 'AllowAbsolute Pkg 'File -> Handle -> IO a
action (String -> SymbolicPathX 'AllowAbsolute Pkg 'File
mkRelToPkg String
fn) Handle
h))
where
i :: SymbolicPath Pkg ('Dir tmpDir) -> String
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir) -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
mkRelToPkg :: FilePath -> SymbolicPath Pkg File
mkRelToPkg :: String -> SymbolicPathX 'AllowAbsolute Pkg 'File
mkRelToPkg String
fp =
SymbolicPath Pkg ('Dir tmpDir)
tmpDir SymbolicPath Pkg ('Dir tmpDir)
-> RelativePath tmpDir 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> String -> RelativePath tmpDir 'File
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx (String -> String
takeFileName String
fp)
withTempDirectory
:: Verbosity
-> FilePath
-> String
-> (FilePath -> IO a)
-> IO a
withTempDirectory :: forall a. Verbosity -> String -> String -> (String -> IO a) -> IO a
withTempDirectory Verbosity
verb String
targetDir String
template String -> 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))
-> String
-> (SymbolicPath Pkg ('Dir (ZonkAny 1)) -> IO a)
-> IO a
forall tmpDir1 tmpDir2 a.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1)
-> String
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwd
Verbosity
verb
Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
(String -> SymbolicPath Pkg ('Dir (ZonkAny 2))
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
targetDir)
String
template
(String -> IO a
f (String -> IO a)
-> (SymbolicPath Pkg ('Dir (ZonkAny 1)) -> String)
-> SymbolicPath Pkg ('Dir (ZonkAny 1))
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg ('Dir (ZonkAny 1)) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
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)
-> String
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir tmpDir1)
targetDir String
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)
-> String
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
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
Verbosity
verbosity
TempFileOptions
defaultTempFileOptions
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
SymbolicPath Pkg ('Dir tmpDir1)
targetDir
String
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 -> String -> String -> (String -> IO a) -> IO a
withTempDirectoryEx Verbosity
verbosity TempFileOptions
opts String
targetDir String
template String -> 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))
-> String
-> (SymbolicPath Pkg ('Dir (ZonkAny 3)) -> IO a)
-> IO a
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 Verbosity
verbosity TempFileOptions
opts Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (String -> SymbolicPath Pkg ('Dir (ZonkAny 4))
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
targetDir) String
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 -> String -> IO a
f (SymbolicPath Pkg ('Dir (ZonkAny 3)) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
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)
-> String
-> (SymbolicPath Pkg ('Dir tmpDir2) -> IO a)
-> IO a
withTempDirectoryCwdEx Verbosity
_verbosity TempFileOptions
opts Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir tmpDir1)
targetDir String
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 String -> (String -> IO ()) -> (String -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket
(String -> String -> IO String
createTempDirectory (SymbolicPath Pkg ('Dir tmpDir1) -> String
i SymbolicPath Pkg ('Dir tmpDir1)
targetDir) String
template)
( \String
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
$
String -> IO ()
removeDirectoryRecursive (SymbolicPath Pkg ('Dir tmpDir1) -> String
i SymbolicPath Pkg ('Dir tmpDir1)
targetDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
tmpDirRelPath)
)
((String -> HasCallStack => IO a) -> WithCallStack (String -> IO a)
forall a b.
(a -> WithCallStack (IO b)) -> WithCallStack (a -> IO b)
withLexicalCallStack (\String
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)
-> RelativePath tmpDir1 ('Dir tmpDir2)
-> SymbolicPath Pkg ('Dir tmpDir2)
forall p q r. PathLike p q r => p -> q -> r
</> String -> RelativePath tmpDir1 ('Dir tmpDir2)
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx String
tmpDirRelPath))
where
i :: SymbolicPath Pkg ('Dir tmpDir1) -> String
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir tmpDir1) -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
rewriteFileEx :: Verbosity -> FilePath -> String -> IO ()
rewriteFileEx :: Verbosity -> String -> String -> IO ()
rewriteFileEx Verbosity
verbosity String
path =
Verbosity -> String -> ByteString -> IO ()
rewriteFileLBS Verbosity
verbosity String
path (ByteString -> IO ()) -> (String -> ByteString) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
toUTF8LBS
rewriteFileLBS :: Verbosity -> FilePath -> BS.ByteString -> IO ()
rewriteFileLBS :: Verbosity -> String -> ByteString -> IO ()
rewriteFileLBS Verbosity
verbosity String
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
$ String -> IO ByteString
BS.readFile String
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
$ String -> ByteString -> IO ()
writeFileAtomic String
path ByteString
newContent
| Bool
otherwise =
IOException -> IO ()
forall a. HasCallStack => IOException -> IO a
ioError IOException
e
shortRelativePath :: FilePath -> FilePath -> FilePath
shortRelativePath :: String -> String -> String
shortRelativePath String
from String
to =
case [String] -> [String] -> ([String], [String])
forall a. Eq a => [a] -> [a] -> ([a], [a])
dropCommonPrefix (String -> [String]
splitDirectories String
from) (String -> [String]
splitDirectories String
to) of
([String]
stuff, [String]
path) -> [String] -> String
joinPath ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall a b. a -> b -> a
const String
"..") [String]
stuff [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
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 :: String -> String
dropExeExtension String
filepath =
let exts :: [String]
exts = [String
ext | String
ext <- [String]
exeExtensions, String
ext String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
""]
in String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
filepath (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ do
ext <- (String -> Bool) -> [String] -> Maybe String
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (String -> String -> Bool
`FilePath.isExtensionOf` String
filepath) [String]
exts
ext `FilePath.stripExtension` filepath
exeExtensions :: [String]
exeExtensions :: [String]
exeExtensions = case (Arch
buildArch, OS
buildOS) of
(Arch
_, OS
Windows) -> [String
"", String
"exe"]
(Arch
_, OS
Ghcjs) -> [String
"", String
"exe"]
(Arch
Wasm32, OS
_) -> [String
"", String
"wasm"]
(Arch, OS)
_ -> [String
""]
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 :: String
pkgDir = String
-> (SymbolicPath CWD ('Dir Pkg) -> String)
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"." SymbolicPath CWD ('Dir Pkg) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbPkgDir
files <- String -> IO [String]
getDirectoryContents String
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)
[String
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
$ String -> RelativePath Pkg 'File
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx String
cabalFile)
[String]
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
$ [String] -> CabalException
MultiDesc [String]
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))
-> SymbolicPath Pkg ('Dir Build)
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
findHookedPackageDesc Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Build)
dir = do
files <- String -> IO [String]
getDirectoryContents (String -> IO [String]) -> String -> IO [String]
forall a b. (a -> b) -> a -> b
$ Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Build) -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath 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
$ String -> CabalException
MultipleFilesWithExtension String
buildInfoExt
buildInfoExt :: String
buildInfoExt :: String
buildInfoExt = String
".buildinfo"