Cabal-2.2.0.0: A framework for packaging Haskell software

CopyrightIsaac Jones Simon Marlow 2003-2004
LicenseBSD3 portions Copyright (c) 2007, Galois Inc.
Maintainer[email protected]
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple.Utils

Contents

Description

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

Documentation

logging and errors

die :: String -> IO a Source #

Deprecated: Messages thrown with die can't be controlled with Verbosity; use die' instead, or dieNoVerbosity if Verbosity truly is not available

dieWithLocation :: FilePath -> Maybe Int -> String -> IO a Source #

Deprecated: Messages thrown with dieWithLocation can't be controlled with Verbosity; use dieWithLocation' instead

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.

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.

noticeDoc :: Verbosity -> Doc -> IO () Source #

Pretty-print a Doc status message at normal verbosity level. Use this if you need fancy formatting.

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.

chattyTry Source #

Arguments

:: String

a description of the action we were attempting

-> IO ()

the action itself

-> IO () 

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.)

exceptions

handleDoesNotExist :: a -> NoCallStackIO a -> NoCallStackIO a Source #

Run an IO computation, returning e if it raises a "file does not exist" error.

running programs

rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String Source #

Run a command and return its output.

The output is assumed to be text in the locale encoding.

rawSystemStdInOut Source #

Arguments

:: 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

output in binary mode

-> IO (IOData, String, ExitCode)

output, errors, exit

Run a command and return its output, errors and exit status. Optionally also supply some input. Also provides control over whether the binary/text mode of the input and output.

rawSystemIOWithEnv Source #

Arguments

:: 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 

createProcessWithEnv Source #

Arguments

:: Verbosity 
-> FilePath 
-> [String] 
-> Maybe FilePath

New working dir or inherit

-> Maybe [(String, String)]

New environment or inherit

-> StdStream

stdin

-> StdStream

stdout

-> StdStream

stderr

-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)

Any handles created for stdin, stdout, or stderr with CreateProcess, and a handle to the process.

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

findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath) Source #

Deprecated: No longer used within Cabal, try findProgramOnSearchPath

Look for a program on the path.

findProgramVersion Source #

Arguments

:: 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

data IOData Source #

Represents either textual or binary data passed via I/O functions which support binary/text mode

Since: 2.2.0

Constructors

IODataText String

How Text gets encoded is usually locale-dependent.

IODataBinary ByteString

Raw binary which gets read/written in binary mode.

Instances
NFData IOData Source # 
Instance details

Methods

rnf :: IOData -> () #

copying files

smartCopySources :: Verbosity -> [FilePath] -> FilePath -> [ModuleName] -> [String] -> IO () Source #

Deprecated: Use findModuleFiles and copyFiles or installOrdinaryFiles

createDirectoryIfMissingVerbose Source #

Arguments

:: Verbosity 
-> Bool

Create its parents too?

-> FilePath 
-> IO () 

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.

copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO () Source #

Deprecated: You probably want installDirectoryContents instead

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.

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.

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 -> NoCallStackIO Bool Source #

Like doesFileExist, but also checks that the file is executable.

file names

currentDir :: FilePath Source #

The path name that represents the current directory. In Unix, it's ".", but this is system-specific. (E.g. AmigaOS uses the empty string "" for the current directory.)

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 platform.

finding files

findFile Source #

Arguments

:: [FilePath]

search locations

-> FilePath

File Name

-> IO FilePath 

Find a file by looking in a search path. The file path must match exactly.

findFileWithExtension :: [String] -> [FilePath] -> FilePath -> NoCallStackIO (Maybe FilePath) 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.

findFileWithExtension' :: [String] -> [FilePath] -> FilePath -> NoCallStackIO (Maybe (FilePath, FilePath)) 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.

findModuleFile Source #

Arguments

:: [FilePath]

build prefix (location of objects)

-> [String]

search suffixes

-> ModuleName

module

-> IO (FilePath, FilePath) 

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.

findModuleFiles Source #

Arguments

:: [FilePath]

build prefix (location of objects)

-> [String]

search suffixes

-> [ModuleName]

modules

-> IO [(FilePath, FilePath)] 

Finds the files corresponding to a list of Haskell module names.

As findModuleFile 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

isInSearchPath :: FilePath -> NoCallStackIO Bool Source #

Is this directory in the system search path?

simple file globbing

data FileGlob Source #

Constructors

NoGlob FilePath

No glob at all, just an ordinary file

FileGlob FilePath String

dir prefix and extension, like "foo/bar/*.baz" corresponds to FileGlob "foo/bar" ".baz"

modification time

moreRecentFile :: FilePath -> FilePath -> NoCallStackIO 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 -> NoCallStackIO 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.

Constructors

TempFileOptions 

Fields

withTempFile Source #

Arguments

:: FilePath

Temp dir to create the file in

-> String

File name template. See openTempFile.

-> (FilePath -> Handle -> IO a) 
-> IO a 

Use a temporary filename that doesn't already exist.

withTempFileEx Source #

Arguments

:: TempFileOptions 
-> FilePath

Temp dir to create the file in

-> String

File name template. See openTempFile.

-> (FilePath -> 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.

withTempDirectoryEx :: Verbosity -> TempFileOptions -> FilePath -> String -> (FilePath -> IO a) -> IO a Source #

A version of withTempDirectory that additionally takes a TempFileOptions argument.

.cabal and .buildinfo files

defaultPackageDesc :: Verbosity -> IO FilePath Source #

Package description file (pkgname.cabal)

findPackageDesc Source #

Arguments

:: FilePath

Where to look

-> NoCallStackIO (Either String FilePath)

pkgname.cabal

Find a package description file in the given directory. Looks for .cabal files.

tryFindPackageDesc :: FilePath -> IO FilePath Source #

Like findPackageDesc, but calls die in case of error.

defaultHookedPackageDesc :: IO (Maybe FilePath) Source #

Deprecated: Use findHookedPackageDesc with the proper base directory instead

Optional auxiliary package information file (pkgname.buildinfo)

findHookedPackageDesc Source #

Arguments

:: FilePath

Directory to search

-> IO (Maybe FilePath)

dir/pkgname.buildinfo, if present

Find auxiliary package information in the given directory. Looks for .buildinfo files.

reading and writing files safely

withFileContents :: FilePath -> (String -> NoCallStackIO a) -> NoCallStackIO a Source #

Gets the contents of a file, but guarantee that it gets closed.

The file is read lazily but if it is not fully consumed by the action then the remaining input is truncated and the file is closed.

writeFileAtomic :: FilePath -> ByteString -> NoCallStackIO () Source #

Writes a file atomically.

The file is either written successfully or an IO exception is raised and the original file is left unchanged.

On windows it is not possible to delete a file that is open by a process. This case will give an IO exception but the atomic property is not affected.

rewriteFile :: FilePath -> String -> IO () Source #

Deprecated: Use rewriteFileEx so that Verbosity is respected

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: the file is assumed to be ASCII-encoded.

Unicode

fromUTF8BS :: ByteString -> String Source #

Decode String from UTF8-encoded ByteString

Invalid data in the UTF8 stream (this includes code-points U+D800 through U+DFFF) will be decoded as the replacement character (U+FFFD).

toUTF8BS :: String -> ByteString Source #

Encode String to to UTF8-encoded ByteString

Code-points in the U+D800-U+DFFF range will be encoded as the replacement character (i.e. U+FFFD).

readUTF8File :: FilePath -> NoCallStackIO String Source #

Reads a UTF8 encoded text file as a Unicode String

Reads lazily using ordinary readFile.

withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a Source #

Reads a UTF8 encoded text file as a Unicode String

Same behaviour as withFileContents.

writeUTF8File :: FilePath -> String -> NoCallStackIO () Source #

Writes a Unicode String as a UTF8 encoded text file.

Uses writeFileAtomic, so provides the same guarantees.

normaliseLineEndings :: String -> String Source #

Fix different systems silly line ending conventions

BOM

ignoreBOM :: String -> String Source #

Ignore a Unicode byte order mark (BOM) at the beginning of the input

generic utils

dropWhileEndLE :: (a -> Bool) -> [a] -> [a] Source #

dropWhileEndLE p is equivalent to reverse . dropWhile p . reverse, but quite a bit faster. The difference between "Data.List.dropWhileEnd" and this version is that the one in Data.List is strict in elements, but spine-lazy, while this one is spine-strict but lazy in elements. That's what LE stands for - "lazy in elements".

Example:

>>> tail $ Data.List.dropWhileEnd (<3) [undefined, 5, 4, 3, 2, 1]
*** Exception: Prelude.undefined
...
>>> tail $ dropWhileEndLE (<3) [undefined, 5, 4, 3, 2, 1]
[5,4,3]
>>> take 3 $ Data.List.dropWhileEnd (<3) [5, 4, 3, 2, 1, undefined]
[5,4,3]
>>> take 3 $ dropWhileEndLE (<3) [5, 4, 3, 2, 1, undefined]
*** Exception: Prelude.undefined
...

takeWhileEndLE :: (a -> Bool) -> [a] -> [a] Source #

takeWhileEndLE p is equivalent to reverse . takeWhile p . reverse, but is usually faster (as well as being easier to read).

equating :: Eq a => (b -> a) -> b -> b -> Bool Source #

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

intercalate :: [a] -> [[a]] -> [a] #

intercalate xs xss is equivalent to (concat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

>>> intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"

lowercase :: String -> String Source #

Lower case string

>>> lowercase "Foobar"
"foobar"

listUnion :: Ord a => [a] -> [a] -> [a] Source #

Like "Data.List.union", but has O(n log n) complexity instead of O(n^2).

listUnionRight :: Ord a => [a] -> [a] -> [a] Source #

A right-biased version of listUnion.

Example:

>>> listUnion [1,2,3,4,3] [2,1,1]
[1,2,3,4,3]
>>> listUnionRight [1,2,3,4,3] [2,1,1]
[4,3,2,1,1]

ordNub :: Ord a => [a] -> [a] Source #

Like nub, but has O(n log n) complexity instead of O(n^2). Code for ordNub and listUnion taken from Niklas Hambüchen's ordnub package.

ordNubBy :: Ord b => (a -> b) -> [a] -> [a] Source #

Like ordNub and nubBy. Selects a key for each element and takes the nub based on that key.

ordNubRight :: Ord a => [a] -> [a] Source #

A right-biased version of ordNub.

Example:

>>> ordNub [1,2,1] :: [Int]
[1,2]
>>> ordNubRight [1,2,1] :: [Int]
[2,1]

safeTail :: [a] -> [a] Source #

A total variant of tail.

wrapText :: String -> String Source #

Wraps text to the default line width. Existing newlines are preserved.

wrapLine :: Int -> [String] -> [[String]] Source #

Wraps a list of words to a list of lines of words of a particular width.

FilePath stuff

isAbsoluteOnAnyPlatform :: FilePath -> Bool Source #

isAbsoluteOnAnyPlatform and isRelativeOnAnyPlatform are like isAbsolute and isRelative but have platform independent heuristics. The System.FilePath exists in two versions, Windows and Posix. The two versions don't agree on what is a relative path and we don't know if we're given Windows or Posix paths. This results in false positives when running on Posix and inspecting Windows paths, like the hackage server does. System.FilePath.Posix.isAbsolute "C:\hello" == False System.FilePath.Windows.isAbsolute "/hello" == False This means that we would treat paths that start with "/" to be absolute. On Posix they are indeed absolute, while on Windows they are not.

The portable versions should be used when we might deal with paths that are from another OS than the host OS. For example, the Hackage Server deals with both Windows and Posix paths while performing the PackageDescription checks. In contrast, when we run 'cabal configure' we do expect the paths to be correct for our OS and we should not have to use the platform independent heuristics.