Copyright | Isaac Jones Simon Marlow 2003-2004 |
---|---|
License | BSD3 portions Copyright (c) 2007, Galois Inc. |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A large and somewhat miscellaneous collection of utility functions used
throughout the rest of the Cabal lib and in other tools that use the Cabal
lib like cabal-install
. It has a very simple set of logging actions. It
has low level functions for running programs, a bunch of wrappers for
various directory and file functions that do extra logging.
Synopsis
- cabalVersion :: Version
- dieNoVerbosity :: String -> IO a
- die' :: Verbosity -> String -> IO a
- dieWithException :: (HasCallStack, Show a1, Typeable a1, Exception (VerboseException a1)) => Verbosity -> a1 -> IO a
- dieWithLocation' :: Verbosity -> FilePath -> Maybe Int -> String -> IO a
- dieNoWrap :: Verbosity -> String -> IO a
- topHandler :: IO a -> IO a
- topHandlerWith :: forall a. (SomeException -> IO a) -> IO a -> IO a
- warn :: Verbosity -> String -> IO ()
- warnError :: Verbosity -> String -> IO ()
- notice :: Verbosity -> String -> IO ()
- noticeNoWrap :: Verbosity -> String -> IO ()
- noticeDoc :: Verbosity -> Doc -> IO ()
- setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
- info :: Verbosity -> String -> IO ()
- infoNoWrap :: Verbosity -> String -> IO ()
- debug :: Verbosity -> String -> IO ()
- debugNoWrap :: Verbosity -> String -> IO ()
- chattyTry :: String -> IO () -> IO ()
- annotateIO :: Verbosity -> IO a -> IO a
- exceptionWithMetadata :: CallStack -> POSIXTime -> Verbosity -> String -> String
- withOutputMarker :: Verbosity -> String -> String
- handleDoesNotExist :: a -> IO a -> IO a
- ignoreSigPipe :: IO () -> IO ()
- rawSystemExit :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> FilePath -> [String] -> IO ()
- rawSystemExitCode :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> FilePath -> [String] -> Maybe [(String, String)] -> IO ExitCode
- rawSystemProc :: Verbosity -> CreateProcess -> IO ExitCode
- rawSystemProcAction :: Verbosity -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a) -> IO (ExitCode, a)
- rawSystemExitWithEnv :: Verbosity -> FilePath -> [String] -> [(String, String)] -> IO ()
- rawSystemExitWithEnvCwd :: Verbosity -> Maybe (SymbolicPath CWD to) -> FilePath -> [String] -> [(String, String)] -> IO ()
- rawSystemStdout :: forall mode. KnownIODataMode mode => Verbosity -> FilePath -> [String] -> IO mode
- rawSystemStdInOut :: KnownIODataMode mode => Verbosity -> FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> Maybe IOData -> IODataMode mode -> IO (mode, String, ExitCode)
- rawSystemIOWithEnv :: Verbosity -> FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ExitCode
- rawSystemIOWithEnvAndAction :: Verbosity -> FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> IO a -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO (ExitCode, a)
- fromCreatePipe :: Maybe Handle -> Handle
- maybeExit :: IO ExitCode -> IO ()
- xargs :: Int -> ([String] -> IO ()) -> [String] -> [String] -> IO ()
- findProgramVersion :: String -> (String -> String) -> Verbosity -> FilePath -> IO (Maybe Version)
- data IOData
- class NFData mode => KnownIODataMode mode where
- hGetIODataContents :: Handle -> IO mode
- toIOData :: mode -> IOData
- iodataMode :: IODataMode mode
- data IODataMode mode where
- data VerboseException a = VerboseException CallStack POSIXTime Verbosity a
- createDirectoryIfMissingVerbose :: Verbosity -> Bool -> FilePath -> IO ()
- copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
- copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
- copyFileTo :: Verbosity -> FilePath -> FilePath -> IO ()
- copyFileToCwd :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir target) -> RelativePath Pkg File -> IO ()
- installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
- installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
- installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
- installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
- installExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
- installMaybeExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
- installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
- copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO ()
- doesExecutableExist :: FilePath -> IO Bool
- setFileOrdinary :: FilePath -> IO ()
- setFileExecutable :: FilePath -> IO ()
- shortRelativePath :: FilePath -> FilePath -> FilePath
- dropExeExtension :: FilePath -> FilePath
- exeExtensions :: [String]
- findFileEx :: forall searchDir allowAbsolute. Verbosity -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (SymbolicPathX allowAbsolute Pkg File)
- findFileCwd :: forall searchDir allowAbsolute. Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (SymbolicPathX allowAbsolute Pkg File)
- findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
- newtype Suffix = Suffix String
- findFileWithExtension :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg File))
- findFileCwdWithExtension :: forall searchDir allowAbsolute. Maybe (SymbolicPath CWD (Dir Pkg)) -> [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg File))
- findFileWithExtension' :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File))
- 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))
- findAllFilesWithExtension :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO [SymbolicPathX allowAbsolute Pkg File]
- findAllFilesCwdWithExtension :: forall searchDir allowAbsolute. Maybe (SymbolicPath CWD (Dir Pkg)) -> [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO [SymbolicPathX allowAbsolute Pkg File]
- findModuleFileEx :: forall searchDir allowAbsolute. Verbosity -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> [Suffix] -> ModuleName -> IO (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)
- 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)
- findModuleFilesEx :: forall searchDir allowAbsolute. Verbosity -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> [Suffix] -> [ModuleName] -> IO [(SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)]
- 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)]
- getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
- isInSearchPath :: FilePath -> IO Bool
- addLibraryPath :: OS -> [FilePath] -> [(String, String)] -> [(String, String)]
- moreRecentFile :: FilePath -> FilePath -> IO Bool
- existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool
- data TempFileOptions = TempFileOptions {}
- defaultTempFileOptions :: TempFileOptions
- withTempFile :: FilePath -> String -> (FilePath -> Handle -> IO a) -> IO a
- withTempFileCwd :: 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 -> (SymbolicPath Pkg File -> Handle -> IO a) -> IO a
- withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a
- withTempDirectoryCwd :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir tmpDir1) -> String -> (SymbolicPath Pkg (Dir tmpDir2) -> IO a) -> IO a
- withTempDirectoryEx :: Verbosity -> TempFileOptions -> FilePath -> String -> (FilePath -> 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
- createTempDirectory :: FilePath -> String -> IO FilePath
- defaultPackageDescCwd :: Verbosity -> IO (RelativePath Pkg File)
- findPackageDesc :: Maybe (SymbolicPath CWD (Dir Pkg)) -> IO (Either CabalException (RelativePath Pkg File))
- tryFindPackageDesc :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> IO (RelativePath Pkg File)
- findHookedPackageDesc :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir Build) -> IO (Maybe (SymbolicPath Pkg File))
- withFileContents :: FilePath -> (String -> IO a) -> IO a
- writeFileAtomic :: FilePath -> ByteString -> IO ()
- rewriteFileEx :: Verbosity -> FilePath -> String -> IO ()
- rewriteFileLBS :: Verbosity -> FilePath -> ByteString -> IO ()
- fromUTF8BS :: ByteString -> String
- fromUTF8LBS :: ByteString -> String
- toUTF8BS :: String -> ByteString
- toUTF8LBS :: String -> ByteString
- readUTF8File :: FilePath -> IO String
- withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
- writeUTF8File :: FilePath -> String -> IO ()
- normaliseLineEndings :: String -> String
- ignoreBOM :: String -> String
- dropWhileEndLE :: (a -> Bool) -> [a] -> [a]
- takeWhileEndLE :: (a -> Bool) -> [a] -> [a]
- equating :: Eq a => (b -> a) -> b -> b -> Bool
- comparing :: Ord a => (b -> a) -> b -> b -> Ordering
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- intercalate :: [a] -> [[a]] -> [a]
- lowercase :: String -> String
- listUnion :: Ord a => [a] -> [a] -> [a]
- listUnionRight :: Ord a => [a] -> [a] -> [a]
- ordNub :: Ord a => [a] -> [a]
- ordNubBy :: Ord b => (a -> b) -> [a] -> [a]
- ordNubRight :: Ord a => [a] -> [a]
- safeHead :: [a] -> Maybe a
- safeTail :: [a] -> [a]
- safeLast :: [a] -> Maybe a
- safeInit :: [a] -> [a]
- unintersperse :: Char -> String -> [String]
- wrapText :: String -> String
- wrapLine :: Int -> [String] -> [[String]]
- isAbsoluteOnAnyPlatform :: FilePath -> Bool
- isRelativeOnAnyPlatform :: FilePath -> Bool
- exceptionWithCallStackPrefix :: CallStack -> Verbosity -> String -> String
Documentation
logging and errors
dieNoVerbosity :: String -> IO a Source #
dieWithException :: (HasCallStack, Show a1, Typeable a1, Exception (VerboseException a1)) => Verbosity -> a1 -> IO a Source #
topHandler :: IO a -> IO a Source #
topHandlerWith :: forall a. (SomeException -> IO a) -> IO a -> IO a Source #
warn :: Verbosity -> String -> IO () Source #
Non fatal conditions that may be indicative of an error or problem.
We display these at the normal
verbosity level.
warnError :: Verbosity -> String -> IO () Source #
Like warn
, but prepend Error: …
instead of Waring: …
before the
the message. Useful when you want to highlight the condition is an error
but do not want to quit the program yet.
notice :: Verbosity -> String -> IO () Source #
Useful status messages.
We display these at the normal
verbosity level.
This is for the ordinary helpful status messages that users see. Just enough information to know that things are working but not floods of detail.
noticeNoWrap :: Verbosity -> String -> IO () Source #
Display a message at normal
verbosity level, but without
wrapping.
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO () Source #
Display a "setup status message". Prefer using setupMessage' if possible.
info :: Verbosity -> String -> IO () Source #
More detail on the operation of some action.
We display these messages when the verbosity level is verbose
debug :: Verbosity -> String -> IO () Source #
Detailed internal debugging information
We display these messages when the verbosity level is deafening
debugNoWrap :: Verbosity -> String -> IO () Source #
A variant of debug
that doesn't perform the automatic line
wrapping. Produces better output in some cases.
Perform an IO action, catching any IO exceptions and printing an error if one occurs.
annotateIO :: Verbosity -> IO a -> IO a Source #
Given a block of IO code that may raise an exception, annotate it with the metadata from the current scope. Use this as close to external code that raises IO exceptions as possible, since this function unconditionally wraps the error message with a trace (so it is NOT idempotent.)
exceptionWithMetadata :: CallStack -> POSIXTime -> Verbosity -> String -> String Source #
Add all necessary metadata to a logging message
withOutputMarker :: Verbosity -> String -> String Source #
Wrap output with a marker if +markoutput
verbosity flag is set.
NB: Why is markoutput done with start/end markers, and not prefixes?
Markers are more convenient to add (if we want to add prefixes,
we have to lines
and then map
; here's it's just some
concatenates). Note that even in the prefix case, we can't
guarantee that the markers are unambiguous, because some of
Cabal's output comes straight from external programs, where
we don't have the ability to interpose on the output.
This is used by withMetadata
exceptions
handleDoesNotExist :: a -> IO a -> IO a Source #
Run an IO computation, returning e
if it raises a "file
does not exist" error.
ignoreSigPipe :: IO () -> IO () Source #
Ignore SIGPIPE in a subcomputation.
running programs
rawSystemExit :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> FilePath -> [String] -> IO () Source #
Execute the given command with the given arguments, exiting with the same exit code if the command fails.
rawSystemExitCode :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> FilePath -> [String] -> Maybe [(String, String)] -> IO ExitCode Source #
Execute the given command with the given arguments, returning the command's exit code.
rawSystemProc :: Verbosity -> CreateProcess -> IO ExitCode Source #
Execute the given command with the given arguments, returning the command's exit code.
Create the process argument with proc
to ensure consistent options with other rawSystem
functions in this
module.
rawSystemProcAction :: Verbosity -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> IO a) -> IO (ExitCode, a) Source #
Execute the given command with the given arguments, returning
the command's exit code. action
is executed while the command
is running, and would typically be used to communicate with the
process through pipes.
Create the process argument with proc
to ensure consistent options with other rawSystem
functions in this
module.
rawSystemExitWithEnv :: Verbosity -> FilePath -> [String] -> [(String, String)] -> IO () Source #
Execute the given command with the given arguments and environment, exiting with the same exit code if the command fails.
rawSystemExitWithEnvCwd :: Verbosity -> Maybe (SymbolicPath CWD to) -> FilePath -> [String] -> [(String, String)] -> IO () Source #
Like rawSystemExitWithEnv
, but setting a working directory.
rawSystemStdout :: forall mode. KnownIODataMode mode => Verbosity -> FilePath -> [String] -> IO mode Source #
Execute the given command with the given arguments, returning the command's output. Exits if the command exits with error.
Provides control over the binary/text mode of the output.
:: KnownIODataMode mode | |
=> Verbosity | |
-> FilePath | Program location |
-> [String] | Arguments |
-> Maybe FilePath | New working dir or inherit |
-> Maybe [(String, String)] | New environment or inherit |
-> Maybe IOData | input text and binary mode |
-> IODataMode mode | iodata mode, acts as proxy |
-> IO (mode, String, ExitCode) | output, errors, exit |
Execute the given command with the given arguments, returning the command's output, errors and exit code.
Optional arguments allow setting working directory, environment and command input.
Provides control over the binary/text mode of the input and output.
:: Verbosity | |
-> FilePath | |
-> [String] | |
-> Maybe FilePath | New working dir or inherit |
-> Maybe [(String, String)] | New environment or inherit |
-> Maybe Handle | stdin |
-> Maybe Handle | stdout |
-> Maybe Handle | stderr |
-> IO ExitCode |
Execute the given command with the given arguments, returning the command's exit code.
Optional arguments allow setting working directory, environment and input and output handles.
rawSystemIOWithEnvAndAction Source #
:: Verbosity | |
-> FilePath | |
-> [String] | |
-> Maybe FilePath | New working dir or inherit |
-> Maybe [(String, String)] | New environment or inherit |
-> IO a | action to perform after process is created, but before |
-> Maybe Handle | stdin |
-> Maybe Handle | stdout |
-> Maybe Handle | stderr |
-> IO (ExitCode, a) |
Execute the given command with the given arguments, returning
the command's exit code. action
is executed while the command
is running, and would typically be used to communicate with the
process through pipes.
Optional arguments allow setting working directory, environment and input and output handles.
fromCreatePipe :: Maybe Handle -> Handle Source #
fromJust for dealing with 'Maybe Handle' values as obtained via
CreatePipe
. Creating a pipe using CreatePipe
guarantees
a Just
value for the corresponding handle.
maybeExit :: IO ExitCode -> IO () Source #
Helper to use with one of the rawSystem
variants, and exit
unless the command completes successfully.
xargs :: Int -> ([String] -> IO ()) -> [String] -> [String] -> IO () Source #
Like the Unix xargs program. Useful for when we've got very long command lines that might overflow an OS limit on command line length and so you need to invoke a command multiple times to get all the args in.
Use it with either of the rawSystem variants above. For example:
xargs (32*1024) (rawSystemExit verbosity) prog fixedArgs bigArgs
:: String | version args |
-> (String -> String) | function to select version number from program output |
-> Verbosity | |
-> FilePath | location |
-> IO (Maybe Version) |
Look for a program and try to find it's version number. It can accept either an absolute path or the name of a program binary, in which case we will look for the program on the path.
IOData
re-export
Represents either textual or binary data passed via I/O functions which support binary/text mode
Since: 2.2
IODataText String | How Text gets encoded is usually locale-dependent. |
IODataBinary ByteString | Raw binary which gets read/written in binary mode. |
class NFData mode => KnownIODataMode mode where Source #
Since: 2.2
hGetIODataContents :: Handle -> IO mode Source #
IOData
Wrapper for hGetContents
Note: This operation uses lazy I/O. Use NFData
to force all
data to be read and consequently the internal file handle to be
closed.
toIOData :: mode -> IOData Source #
iodataMode :: IODataMode mode Source #
Instances
KnownIODataMode ByteString Source # | |
Defined in Distribution.Utils.IOData hGetIODataContents :: Handle -> IO ByteString Source # toIOData :: ByteString -> IOData Source # | |
a ~ Char => KnownIODataMode [a] Source # | |
Defined in Distribution.Utils.IOData hGetIODataContents :: Handle -> IO [a] Source # toIOData :: [a] -> IOData Source # iodataMode :: IODataMode [a] Source # |
data IODataMode mode where Source #
Phantom-typed GADT representation of the mode of IOData
, containing no
other data.
Since: 3.2
data VerboseException a Source #
Instances
Exception (VerboseException CabalException) Source # | |
Show a => Show (VerboseException a) Source # | |
Defined in Distribution.Simple.Utils showsPrec :: Int -> VerboseException a -> ShowS # show :: VerboseException a -> String # showList :: [VerboseException a] -> ShowS # |
copying files
createDirectoryIfMissingVerbose Source #
Same as createDirectoryIfMissing
but logs at higher verbosity levels.
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO () Source #
Copies a file without copying file permissions. The target file is created with default permissions. Any existing target file is replaced.
At higher verbosity levels it logs an info message.
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () Source #
Copies a bunch of files to a target directory, preserving the directory structure in the target location. The target directories are created if they do not exist.
The files are identified by a pair of base directory and a path relative to that base. It is only the relative part that is preserved in the destination.
For example:
copyFiles normal "dist/src" [("", "src/Foo.hs"), ("dist/build/", "src/Bar.hs")]
This would copy "src/Foo.hs" to "dist/src/src/Foo.hs" and copy "dist/build/src/Bar.hs" to "dist/src/src/Bar.hs".
This operation is not atomic. Any IO failure during the copy (including any missing source files) leaves the target in an unknown state so it is best to use it with a freshly created directory so that it can be simply deleted if anything goes wrong.
copyFileTo :: Verbosity -> FilePath -> FilePath -> IO () Source #
Given a relative path to a file, copy it to the given directory, preserving the relative path and creating the parent directories if needed.
copyFileToCwd :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir target) -> RelativePath Pkg File -> IO () Source #
Given a relative path to a file, copy it to the given directory, preserving the relative path and creating the parent directories if needed.
installing files
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO () Source #
Install an ordinary file. This is like a file copy but the permissions are set appropriately for an installed file. On Unix it is "-rw-r--r--" while on Windows it uses the default permissions for the target directory.
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO () Source #
Install an executable file. This is like a file copy but the permissions are set appropriately for an installed file. On Unix it is "-rwxr-xr-x" while on Windows it uses the default permissions for the target directory.
installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO () Source #
Install a file that may or not be executable, preserving permissions.
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () Source #
This is like copyFiles
but uses installOrdinaryFile
.
installExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () Source #
This is like copyFiles
but uses installExecutableFile
.
installMaybeExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () Source #
This is like copyFiles
but uses installMaybeExecutableFile
.
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO () Source #
This installs all the files in a directory to a target location, preserving the directory layout. All the files are assumed to be ordinary rather than executable files.
copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO () Source #
Recursively copy the contents of one directory to another path.
File permissions
doesExecutableExist :: FilePath -> IO Bool Source #
Like doesFileExist
, but also checks that the file is executable.
setFileOrdinary :: FilePath -> IO () Source #
setFileExecutable :: FilePath -> IO () Source #
file names
dropExeExtension :: FilePath -> FilePath Source #
Drop the extension if it's one of exeExtensions
, or return the path
unchanged.
exeExtensions :: [String] Source #
List of possible executable file extensions on the current build platform.
finding files
:: forall searchDir allowAbsolute. Verbosity | |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | search directories |
-> RelativePath searchDir File | File Name |
-> IO (SymbolicPathX allowAbsolute Pkg File) |
Find a file by looking in a search path. The file path must match exactly.
:: forall searchDir allowAbsolute. Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | working directory |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | search directories |
-> RelativePath searchDir File | File Name |
-> IO (SymbolicPathX allowAbsolute Pkg File) |
Find a file by looking in a search path. The file path must match exactly.
Since: 3.4.0.0
A suffix (or file extension).
Mostly used to decide which preprocessor to use, e.g. files with suffix "y"
are usually processed by the "happy"
build tool.
Instances
Pretty Suffix Source # | |
Defined in Distribution.Simple.PreProcess.Types | |
Structured Suffix Source # | |
Defined in Distribution.Simple.PreProcess.Types structure :: Proxy Suffix -> Structure structureHash' :: Tagged Suffix MD5 | |
IsString Suffix Source # | |
Defined in Distribution.Simple.PreProcess.Types fromString :: String -> Suffix # | |
Generic Suffix Source # | |
Show Suffix Source # | |
Binary Suffix Source # | |
Eq Suffix Source # | |
Ord Suffix Source # | |
type Rep Suffix Source # | |
Defined in Distribution.Simple.PreProcess.Types |
findFileWithExtension :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg File)) Source #
Find a file by looking in a search path with one of a list of possible file extensions. The file base name should be given and it will be tried with each of the extensions in each element of the search path.
findFileCwdWithExtension :: forall searchDir allowAbsolute. Maybe (SymbolicPath CWD (Dir Pkg)) -> [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg File)) Source #
Find a file by looking in a search path with one of a list of possible file extensions.
Since: 3.4.0.0
findFileWithExtension' :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO (Maybe (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)) Source #
Like findFileWithExtension
but returns which element of the search path
the file was found in, and the file path relative to that base directory.
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)) Source #
Like findFileCwdWithExtension
but returns which element of the search path
the file was found in, and the file path relative to that base directory.
findAllFilesWithExtension :: [Suffix] -> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] -> RelativePath searchDir File -> IO [SymbolicPathX allowAbsolute Pkg File] Source #
findAllFilesCwdWithExtension Source #
:: forall searchDir allowAbsolute. Maybe (SymbolicPath CWD (Dir Pkg)) | working directory |
-> [Suffix] | extensions |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | relative search locations |
-> RelativePath searchDir File | basename |
-> IO [SymbolicPathX allowAbsolute Pkg File] |
Since: 3.4.0.0
:: forall searchDir allowAbsolute. Verbosity | |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | build prefix (location of objects) |
-> [Suffix] | search suffixes |
-> ModuleName | module |
-> IO (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File) |
Find the file corresponding to a Haskell module name.
This is similar to findFileWithExtension'
but specialised to a module
name. The function fails if the file corresponding to the module is missing.
:: forall searchDir allowAbsolute. Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | build prefix (location of objects) |
-> [Suffix] | search suffixes |
-> ModuleName | module |
-> IO (SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File) |
Find the file corresponding to a Haskell module name.
This is similar to findFileCwdWithExtension'
but specialised to a module
name. The function fails if the file corresponding to the module is missing.
:: forall searchDir allowAbsolute. Verbosity | |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | build prefix (location of objects) |
-> [Suffix] | search suffixes |
-> [ModuleName] | modules |
-> IO [(SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)] |
Finds the files corresponding to a list of Haskell module names.
As findModuleFile
but for a list of module names.
:: forall searchDir allowAbsolute. Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | |
-> [SymbolicPathX allowAbsolute Pkg (Dir searchDir)] | build prefix (location of objects) |
-> [Suffix] | search suffixes |
-> [ModuleName] | modules |
-> IO [(SymbolicPathX allowAbsolute Pkg (Dir searchDir), RelativePath searchDir File)] |
Finds the files corresponding to a list of Haskell module names.
As findModuleFileCwd
but for a list of module names.
getDirectoryContentsRecursive :: FilePath -> IO [FilePath] Source #
List all the files in a directory and all subdirectories.
The order places files in sub-directories after all the files in their parent directories. The list is generated lazily so is not well defined if the source directory structure changes before the list is used.
environment variables
modification time
moreRecentFile :: FilePath -> FilePath -> IO Bool Source #
Compare the modification times of two files to see if the first is newer than the second. The first file must exist but the second need not. The expected use case is when the second file is generated using the first. In this use case, if the result is True then the second file is out of date.
existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool Source #
Like moreRecentFile
, but also checks that the first file exists.
temp files and dirs
data TempFileOptions Source #
Advanced options for withTempFile
and withTempDirectory
.
TempFileOptions | |
|
:: FilePath | Temp dir to create the file in |
-> String | File name template. See |
-> (FilePath -> Handle -> IO a) | |
-> IO a |
Use a temporary filename that doesn't already exist
:: Maybe (SymbolicPath CWD (Dir Pkg)) | Working directory |
-> SymbolicPath Pkg (Dir tmpDir) | Temp dir to create the file in |
-> String | File name template. See |
-> (SymbolicPath Pkg File -> Handle -> IO a) | |
-> IO a |
Use a temporary filename that doesn't already exist.
:: forall a tmpDir. TempFileOptions | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | Working directory |
-> SymbolicPath Pkg (Dir tmpDir) | Temp dir to create the file in |
-> String | File name template. See |
-> (SymbolicPath Pkg File -> Handle -> IO a) | |
-> IO a |
A version of withTempFile
that additionally takes a TempFileOptions
argument.
withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a Source #
Create and use a temporary directory.
Creates a new temporary directory inside the given directory, making use of the template. The temp directory is deleted after use. For example:
withTempDirectory verbosity "src" "sdist." $ \tmpDir -> do ...
The tmpDir
will be a new subdirectory of the given directory, e.g.
src/sdist.342
.
:: Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | Working directory |
-> SymbolicPath Pkg (Dir tmpDir1) | |
-> String | |
-> (SymbolicPath Pkg (Dir tmpDir2) -> IO a) | |
-> IO a |
Create and use a temporary directory.
Creates a new temporary directory inside the given directory, making use of the template. The temp directory is deleted after use. For example:
withTempDirectory verbosity "src" "sdist." $ \tmpDir -> do ...
The tmpDir
will be a new subdirectory of the given directory, e.g.
src/sdist.342
.
withTempDirectoryEx :: Verbosity -> TempFileOptions -> FilePath -> String -> (FilePath -> IO a) -> IO a Source #
A version of withTempDirectory
that additionally takes a
TempFileOptions
argument.
withTempDirectoryCwdEx Source #
:: forall a tmpDir1 tmpDir2. Verbosity | |
-> TempFileOptions | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | Working directory |
-> SymbolicPath Pkg (Dir tmpDir1) | |
-> String | |
-> (SymbolicPath Pkg (Dir tmpDir2) -> IO a) | |
-> IO a |
A version of withTempDirectoryCwd
that additionally takes a
TempFileOptions
argument.
.cabal and .buildinfo files
defaultPackageDescCwd :: Verbosity -> IO (RelativePath Pkg File) Source #
Package description file (pkgname.cabal
) in the current
working directory.
:: Maybe (SymbolicPath CWD (Dir Pkg)) | package directory |
-> IO (Either CabalException (RelativePath Pkg File)) |
Find a package description file in the given directory. Looks for
.cabal
files.
:: Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | directory in which to look |
-> IO (RelativePath Pkg File) |
Like findPackageDesc
, but calls die
in case of error.
findHookedPackageDesc Source #
:: Verbosity | |
-> Maybe (SymbolicPath CWD (Dir Pkg)) | Working directory |
-> SymbolicPath Pkg (Dir Build) | Directory to search |
-> IO (Maybe (SymbolicPath Pkg File)) | dir |
Find auxiliary package information in the given directory.
Looks for .buildinfo
files.
reading and writing files safely
writeFileAtomic :: FilePath -> ByteString -> IO () #
rewriteFileEx :: Verbosity -> FilePath -> String -> IO () Source #
Write a file but only if it would have new content. If we would be writing the same as the existing content then leave the file as is so that we do not update the file's modification time.
NB: Before Cabal-3.0 the file content was assumed to be ASCII-representable. Since Cabal-3.0 the file is assumed to be UTF-8 encoded.
rewriteFileLBS :: Verbosity -> FilePath -> ByteString -> IO () Source #
Same as rewriteFileEx
but for ByteString
s.
Unicode
fromUTF8BS :: ByteString -> String #
fromUTF8LBS :: ByteString -> String #
toUTF8BS :: String -> ByteString #
toUTF8LBS :: String -> ByteString #
readUTF8File :: FilePath -> IO String #
writeUTF8File :: FilePath -> String -> IO () #
normaliseLineEndings :: String -> String #
BOM
generic utils
dropWhileEndLE :: (a -> Bool) -> [a] -> [a] #
takeWhileEndLE :: (a -> Bool) -> [a] -> [a] #
comparing :: Ord a => (b -> a) -> b -> b -> Ordering #
comparing p x y = compare (p x) (p y)
Useful combinator for use in conjunction with the xxxBy
family
of functions from Data.List, for example:
... sortBy (comparing fst) ...
isInfixOf :: Eq a => [a] -> [a] -> Bool #
The isInfixOf
function takes two lists and returns True
iff the first list is contained, wholly and intact,
anywhere within the second.
>>>
isInfixOf "Haskell" "I really like Haskell."
True>>>
isInfixOf "Ial" "I really like Haskell."
False
For the result to be True
, the first list must be finite;
for the result to be False
, the second list must be finite:
>>>
[20..50] `isInfixOf` [0..]
True>>>
[0..] `isInfixOf` [20..50]
False>>>
[0..] `isInfixOf` [0..]
* Hangs forever *
intercalate :: [a] -> [[a]] -> [a] #
intercalate
xs xss
is equivalent to (
.
It inserts the list concat
(intersperse
xs xss))xs
in between the lists in xss
and concatenates the
result.
>>>
intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"
listUnionRight :: Ord a => [a] -> [a] -> [a] #
ordNubRight :: Ord a => [a] -> [a] #
unintersperse :: Char -> String -> [String] #
FilePath stuff
isAbsoluteOnAnyPlatform :: FilePath -> Bool #
isRelativeOnAnyPlatform :: FilePath -> Bool #