Cabal-1.8.0.2: A framework for packaging Haskell softwareSource codeContentsIndex
Distribution.Simple.Program
Portabilityportable
Maintainercabal-devel@haskell.org
Contents
Program and functions for constructing them
Configured program and related functions
Program invocations
The collection of unconfigured and configured progams
The collection of configured programs we can run
Programs that Cabal knows about
deprecated
Description

This provides an abstraction which deals with configuring and running programs. A Program is a static notion of a known program. A ConfiguredProgram is a Program that has been found on the current machine and is ready to be run (possibly with some user-supplied default args). Configuring a program involves finding its location and if necessary finding its version. There is also a ProgramConfiguration type which holds configured and not-yet configured programs. It is the parameter to lots of actions elsewhere in Cabal that need to look up and run programs. If we had a Cabal monad, the ProgramConfiguration would probably be a reader or state component of it.

The module also defines all the known built-in Programs and the defaultProgramConfiguration which contains them all.

One nice thing about using it is that any program that is registered with Cabal will get some "configure" and ".cabal" helpers like --with-foo-args --foo-path= and extra-foo-args.

There's also good default behavior for trying to find "foo" in PATH, being able to override its location, etc.

There's also a hook for adding programs in a Setup.lhs script. See hookedPrograms in Distribution.Simple.UserHooks. This gives a hook user the ability to get the above flags and such so that they don't have to write all the PATH logic inside Setup.lhs.

Synopsis
data Program = Program {
programName :: String
programFindLocation :: Verbosity -> IO (Maybe FilePath)
programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
programPostConf :: Verbosity -> ConfiguredProgram -> IO [ProgArg]
}
simpleProgram :: String -> Program
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
findProgramVersion :: String -> (String -> String) -> Verbosity -> FilePath -> IO (Maybe Version)
data ConfiguredProgram = ConfiguredProgram {
programId :: String
programVersion :: Maybe Version
programArgs :: [String]
programLocation :: ProgramLocation
}
programPath :: ConfiguredProgram -> FilePath
type ProgArg = String
data ProgramLocation
= UserSpecified {
locationPath :: FilePath
}
| FoundOnSystem {
locationPath :: FilePath
}
runProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO ()
getProgramOutput :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String
data ProgramInvocation = ProgramInvocation {
progInvokePath :: FilePath
progInvokeArgs :: [String]
progInvokeEnv :: [(String, String)]
progInvokeCwd :: Maybe FilePath
progInvokeInput :: Maybe String
progInvokeInputEncoding :: IOEncoding
progInvokeOutputEncoding :: IOEncoding
}
emptyProgramInvocation :: ProgramInvocation
simpleProgramInvocation :: FilePath -> [String] -> ProgramInvocation
programInvocation :: ConfiguredProgram -> [String] -> ProgramInvocation
runProgramInvocation :: Verbosity -> ProgramInvocation -> IO ()
getProgramInvocationOutput :: Verbosity -> ProgramInvocation -> IO String
builtinPrograms :: [Program]
type ProgramConfiguration = ProgramDb
emptyProgramConfiguration :: ProgramConfiguration
defaultProgramConfiguration :: ProgramConfiguration
restoreProgramConfiguration :: [Program] -> ProgramConfiguration -> ProgramConfiguration
addKnownProgram :: Program -> ProgramDb -> ProgramDb
addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb
lookupKnownProgram :: String -> ProgramDb -> Maybe Program
knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)]
userSpecifyPath :: String -> FilePath -> ProgramDb -> ProgramDb
userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDb
userMaybeSpecifyPath :: String -> Maybe FilePath -> ProgramDb -> ProgramDb
userSpecifyArgs :: String -> [ProgArg] -> ProgramDb -> ProgramDb
userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDb
userSpecifiedArgs :: Program -> ProgramDb -> [ProgArg]
lookupProgram :: Program -> ProgramDb -> Maybe ConfiguredProgram
updateProgram :: ConfiguredProgram -> ProgramDb -> ProgramDb
configureProgram :: Verbosity -> Program -> ProgramDb -> IO ProgramDb
configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDb
reconfigurePrograms :: Verbosity -> [(String, FilePath)] -> [(String, [ProgArg])] -> ProgramDb -> IO ProgramDb
requireProgram :: Verbosity -> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (ConfiguredProgram, Version, ProgramDb)
runDbProgram :: Verbosity -> Program -> ProgramDb -> [ProgArg] -> IO ()
getDbProgramOutput :: Verbosity -> Program -> ProgramDb -> [ProgArg] -> IO String
ghcProgram :: Program
ghcPkgProgram :: Program
lhcProgram :: Program
lhcPkgProgram :: Program
nhcProgram :: Program
hmakeProgram :: Program
jhcProgram :: Program
hugsProgram :: Program
ffihugsProgram :: Program
gccProgram :: Program
ranlibProgram :: Program
arProgram :: Program
stripProgram :: Program
happyProgram :: Program
alexProgram :: Program
hsc2hsProgram :: Program
c2hsProgram :: Program
cpphsProgram :: Program
hscolourProgram :: Program
haddockProgram :: Program
greencardProgram :: Program
ldProgram :: Program
tarProgram :: Program
cppProgram :: Program
pkgConfigProgram :: Program
rawSystemProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO ()
rawSystemProgramStdout :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String
rawSystemProgramConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO ()
rawSystemProgramStdoutConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO String
findProgramOnPath :: String -> Verbosity -> IO (Maybe FilePath)
Program and functions for constructing them
data Program Source
Represents a program which can be configured.
Constructors
Program
programName :: StringThe simple name of the program, eg. ghc
programFindLocation :: Verbosity -> IO (Maybe FilePath)A function to search for the program if it's location was not specified by the user. Usually this will just be a
programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)Try to find the version of the program. For many programs this is not possible or is not necessary so it's ok to return Nothing.
programPostConf :: Verbosity -> ConfiguredProgram -> IO [ProgArg]A function to do any additional configuration after we have located the program (and perhaps identified its version). It is allowed to return additional flags that will be passed to the program on every invocation.
simpleProgram :: String -> ProgramSource

Make a simple named program.

By default we'll just search for it in the path and not try to find the version name. You can override these behaviours if necessary, eg:

 simpleProgram "foo" { programFindLocation = ... , programFindVersion ... }
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)Source
Look for a program on the path.
findProgramVersionSource
:: Stringversion args
-> String -> Stringfunction to select version number from program output
-> Verbosity
-> FilePathlocation
-> 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.
Configured program and related functions
data ConfiguredProgram Source
Constructors
ConfiguredProgram
programId :: StringJust the name again
programVersion :: Maybe VersionThe version of this program, if it is known.
programArgs :: [String]Default command-line args for this program. These flags will appear first on the command line, so they can be overridden by subsequent flags.
programLocation :: ProgramLocationLocation of the program. eg. /usr/bin/ghc-6.4
show/hide Instances
programPath :: ConfiguredProgram -> FilePathSource
The full path of a configured program.
type ProgArg = StringSource
data ProgramLocation Source
Where a program was found. Also tells us whether it's specifed by user or not. This includes not just the path, but the program as well.
Constructors
UserSpecifiedThe user gave the path to this program, eg. --ghc-path=/usr/bin/ghc-6.6
locationPath :: FilePath
FoundOnSystemThe location of the program, as located by searching PATH.
locationPath :: FilePath
show/hide Instances
runProgramSource
:: VerbosityVerbosity
-> ConfiguredProgramThe program to run
-> [ProgArg]Any extra arguments to add
-> IO ()
Runs the given configured program.
getProgramOutputSource
:: VerbosityVerbosity
-> ConfiguredProgramThe program to run
-> [ProgArg]Any extra arguments to add
-> IO String
Runs the given configured program and gets the output.
Program invocations
data ProgramInvocation Source

Represents a specific invocation of a specific program.

This is used as an intermediate type between deciding how to call a program and actually doing it. This provides the opportunity to the caller to adjust how the program will be called. These invocations can either be run directly or turned into shell or batch scripts.

Constructors
ProgramInvocation
progInvokePath :: FilePath
progInvokeArgs :: [String]
progInvokeEnv :: [(String, String)]
progInvokeCwd :: Maybe FilePath
progInvokeInput :: Maybe String
progInvokeInputEncoding :: IOEncoding
progInvokeOutputEncoding :: IOEncoding
emptyProgramInvocation :: ProgramInvocationSource
simpleProgramInvocation :: FilePath -> [String] -> ProgramInvocationSource
programInvocation :: ConfiguredProgram -> [String] -> ProgramInvocationSource
runProgramInvocation :: Verbosity -> ProgramInvocation -> IO ()Source
getProgramInvocationOutput :: Verbosity -> ProgramInvocation -> IO StringSource
The collection of unconfigured and configured progams
builtinPrograms :: [Program]Source
The default list of programs. These programs are typically used internally to Cabal.
The collection of configured programs we can run
type ProgramConfiguration = ProgramDbSource
emptyProgramConfiguration :: ProgramConfigurationSource
defaultProgramConfiguration :: ProgramConfigurationSource
restoreProgramConfiguration :: [Program] -> ProgramConfiguration -> ProgramConfigurationSource
addKnownProgram :: Program -> ProgramDb -> ProgramDbSource
Add a known program that we may configure later
addKnownPrograms :: [Program] -> ProgramDb -> ProgramDbSource
lookupKnownProgram :: String -> ProgramDb -> Maybe ProgramSource
knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)]Source
userSpecifyPathSource
:: StringProgram name
-> FilePathuser-specified path to the program
-> ProgramDb
-> ProgramDb
User-specify this path. Basically override any path information for this program in the configuration. If it's not a known program ignore it.
userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDbSource
Like userSpecifyPath but for a list of progs and their paths.
userMaybeSpecifyPath :: String -> Maybe FilePath -> ProgramDb -> ProgramDbSource
userSpecifyArgsSource
:: StringProgram name
-> [ProgArg]user-specified args
-> ProgramDb
-> ProgramDb
User-specify the arguments for this program. Basically override any args information for this program in the configuration. If it's not a known program, ignore it..
userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDbSource
Like userSpecifyPath but for a list of progs and their args.
userSpecifiedArgs :: Program -> ProgramDb -> [ProgArg]Source
Get any extra args that have been previously specified for a program.
lookupProgram :: Program -> ProgramDb -> Maybe ConfiguredProgramSource
Try to find a configured program
updateProgram :: ConfiguredProgram -> ProgramDb -> ProgramDbSource
Update a configured program in the database.
configureProgram :: Verbosity -> Program -> ProgramDb -> IO ProgramDbSource

Try to configure a specific program. If the program is already included in the colleciton of unconfigured programs then we use any user-supplied location and arguments. If the program gets configured sucessfully it gets added to the configured collection.

Note that it is not a failure if the program cannot be configured. It's only a failure if the user supplied a location and the program could not be found at that location.

The reason for it not being a failure at this stage is that we don't know up front all the programs we will need, so we try to configure them all. To verify that a program was actually sucessfully configured use requireProgram.

configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDbSource
Try to configure all the known programs that have not yet been configured.
reconfigurePrograms :: Verbosity -> [(String, FilePath)] -> [(String, [ProgArg])] -> ProgramDb -> IO ProgramDbSource
reconfigure a bunch of programs given new user-specified args. It takes the same inputs as userSpecifyPath and userSpecifyArgs and for all progs with a new path it calls configureProgram.
requireProgram :: Verbosity -> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)Source

Check that a program is configured and available to be run.

It raises an exception if the program could not be configured, otherwise it returns the configured program.

requireProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (ConfiguredProgram, Version, ProgramDb)Source

Check that a program is configured and available to be run.

Additionally check that the version of the program number is suitable and return it. For example you could require AnyVersion or orLaterVersion (Version [1,0] [])

It raises an exception if the program could not be configured or the version is unsuitable, otherwise it returns the configured program and its version number.

runDbProgramSource
:: Verbosityverbosity
-> ProgramThe program to run
-> ProgramDblook up the program here
-> [ProgArg]Any extra arguments to add
-> IO ()
Looks up the given program in the program database and runs it.
getDbProgramOutputSource
:: Verbosityverbosity
-> ProgramThe program to run
-> ProgramDblook up the program here
-> [ProgArg]Any extra arguments to add
-> IO String
Looks up the given program in the program database and runs it.
Programs that Cabal knows about
ghcProgram :: ProgramSource
ghcPkgProgram :: ProgramSource
lhcProgram :: ProgramSource
lhcPkgProgram :: ProgramSource
nhcProgram :: ProgramSource
hmakeProgram :: ProgramSource
jhcProgram :: ProgramSource
hugsProgram :: ProgramSource
ffihugsProgram :: ProgramSource
gccProgram :: ProgramSource
ranlibProgram :: ProgramSource
arProgram :: ProgramSource
stripProgram :: ProgramSource
happyProgram :: ProgramSource
alexProgram :: ProgramSource
hsc2hsProgram :: ProgramSource
c2hsProgram :: ProgramSource
cpphsProgram :: ProgramSource
hscolourProgram :: ProgramSource
haddockProgram :: ProgramSource
greencardProgram :: ProgramSource
ldProgram :: ProgramSource
tarProgram :: ProgramSource
cppProgram :: ProgramSource
pkgConfigProgram :: ProgramSource
deprecated
rawSystemProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO ()Source
rawSystemProgramStdout :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO StringSource
rawSystemProgramConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO ()Source
rawSystemProgramStdoutConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO StringSource
findProgramOnPath :: String -> Verbosity -> IO (Maybe FilePath)Source
Produced by Haddock version 2.6.0