| Copyright | Isaac Jones 2006, Duncan Coutts 2007-2009 | 
|---|---|
| Maintainer | cabal-devel@haskell.org | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Distribution.Simple.Program
Contents
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 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.
- data Program = Program {- programName :: String
- programFindLocation :: Verbosity -> ProgramSearchPath -> IO (Maybe (FilePath, [FilePath]))
- programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
- programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
 
- type ProgramSearchPath = [ProgramSearchPathEntry]
- data ProgramSearchPathEntry
- simpleProgram :: String -> Program
- findProgramOnSearchPath :: Verbosity -> ProgramSearchPath -> FilePath -> IO (Maybe (FilePath, [FilePath]))
- defaultProgramSearchPath :: ProgramSearchPath
- findProgramVersion :: String -> (String -> String) -> Verbosity -> FilePath -> IO (Maybe Version)
- data ConfiguredProgram = ConfiguredProgram {}
- programPath :: ConfiguredProgram -> FilePath
- type ProgArg = String
- data ProgramLocation- = UserSpecified { }
- | FoundOnSystem { }
 
- runProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO ()
- getProgramOutput :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String
- suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram
- data ProgramInvocation = ProgramInvocation {}
- 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)]
- getProgramSearchPath :: ProgramDb -> ProgramSearchPath
- setProgramSearchPath :: ProgramSearchPath -> ProgramDb -> ProgramDb
- 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
- lookupProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (Either String (ConfiguredProgram, Version, ProgramDb))
- 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
- ghcjsProgram :: Program
- ghcjsPkgProgram :: Program
- lhcProgram :: Program
- lhcPkgProgram :: Program
- hmakeProgram :: Program
- jhcProgram :: Program
- uhcProgram :: Program
- gccProgram :: 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
- hpcProgram :: 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)
- findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
Program and functions for constructing them
Represents a program which can be configured.
Note: rather than constructing this directly, start with simpleProgram and
 override any extra fields.
Constructors
| Program | |
| Fields 
 | |
type ProgramSearchPath = [ProgramSearchPathEntry] Source #
A search path to use when locating executables. This is analogous
 to the unix $PATH or win32 %PATH% but with the ability to use
 the system default method for finding executables (findExecutable which
 on unix is simply looking on the $PATH but on win32 is a bit more
 complicated).
The default to use is [ProgSearchPathDefault] but you can add extra dirs
 either before, after or instead of the default, e.g. here we add an extra
 dir to search after the usual ones.
['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
data ProgramSearchPathEntry Source #
Constructors
| ProgramSearchPathDir FilePath | A specific dir | 
| ProgramSearchPathDefault | The system default | 
simpleProgram :: String -> Program Source #
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 ... }findProgramOnSearchPath :: Verbosity -> ProgramSearchPath -> FilePath -> IO (Maybe (FilePath, [FilePath])) 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.
Configured program and related functions
data ConfiguredProgram Source #
Represents a program which has been configured and is thus ready to be run.
These are usually made by configuring a Program, but if you have to
 construct one directly then start with simpleConfiguredProgram and
 override any extra fields.
Constructors
| ConfiguredProgram | |
| Fields 
 | |
programPath :: ConfiguredProgram -> FilePath Source #
The full path of a configured program.
data ProgramLocation Source #
Where a program was found. Also tells us whether it's specified by user or not. This includes not just the path, but the program as well.
Constructors
| UserSpecified | The user gave the path to this program, eg. --ghc-path=/usr/bin/ghc-6.6 | 
| Fields | |
| FoundOnSystem | The program was found automatically. | 
| Fields | |
Arguments
| :: Verbosity | Verbosity | 
| -> ConfiguredProgram | The program to run | 
| -> [ProgArg] | Any extra arguments to add | 
| -> IO () | 
Runs the given configured program.
Arguments
| :: Verbosity | Verbosity | 
| -> ConfiguredProgram | The program to run | 
| -> [ProgArg] | Any extra arguments to add | 
| -> IO String | 
Runs the given configured program and gets the output.
suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram Source #
Suppress any extra arguments added by the user.
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 | |
| Fields | |
simpleProgramInvocation :: FilePath -> [String] -> ProgramInvocation Source #
programInvocation :: ConfiguredProgram -> [String] -> ProgramInvocation Source #
runProgramInvocation :: Verbosity -> ProgramInvocation -> IO () Source #
The collection of unconfigured and configured programs
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 = ProgramDb Source #
addKnownProgram :: Program -> ProgramDb -> ProgramDb Source #
Add a known program that we may configure later
knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)] Source #
getProgramSearchPath :: ProgramDb -> ProgramSearchPath Source #
Get the current ProgramSearchPath used by the ProgramDb.
 This is the default list of locations where programs are looked for when
 configuring them. This can be overridden for specific programs (with
 userSpecifyPath), and specific known programs can modify or ignore this
 search path in their own configuration code.
setProgramSearchPath :: ProgramSearchPath -> ProgramDb -> ProgramDb Source #
Change the current ProgramSearchPath used by the ProgramDb.
 This will affect programs that are configured from here on, so you
 should usually set it before configuring any programs.
Arguments
| :: String | Program name | 
| -> FilePath | user-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 -> ProgramDb Source #
Like userSpecifyPath but for a list of progs and their paths.
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 -> ProgramDb Source #
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 ConfiguredProgram Source #
Try to find a configured program
lookupProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (Either String (ConfiguredProgram, Version, ProgramDb)) Source #
Check that a program is configured and available to be run.
Additionally check that the program version number is suitable and return
 it. For example you could require AnyVersion or orLaterVersion
 (Version [1,0] [])
It returns the configured program, its version number and a possibly updated
 ProgramDb. If the program could not be configured or the version is
 unsuitable, it returns an error value.
updateProgram :: ConfiguredProgram -> ProgramDb -> ProgramDb Source #
Update a configured program in the database.
configureProgram :: Verbosity -> Program -> ProgramDb -> IO ProgramDb Source #
Try to configure a specific program. If the program is already included in the collection of unconfigured programs then we use any user-supplied location and arguments. If the program gets configured successfully 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 successfully configured use
 requireProgram.
configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDb Source #
Try to configure all the known programs that have not yet been configured.
reconfigurePrograms :: Verbosity -> [(String, FilePath)] -> [(String, [ProgArg])] -> ProgramDb -> IO ProgramDb Source #
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 #
Like lookupProgramVersion, but raises an exception in case of error
 instead of returning 'Left errMsg'.
Arguments
| :: Verbosity | verbosity | 
| -> Program | The program to run | 
| -> ProgramDb | look up the program here | 
| -> [ProgArg] | Any extra arguments to add | 
| -> IO () | 
Looks up the given program in the program database and runs it.
Arguments
| :: Verbosity | verbosity | 
| -> Program | The program to run | 
| -> ProgramDb | look 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 :: Program Source #
lhcProgram :: Program Source #
jhcProgram :: Program Source #
uhcProgram :: Program Source #
gccProgram :: Program Source #
tarProgram :: Program Source #
cppProgram :: Program Source #
hpcProgram :: Program Source #
deprecated
rawSystemProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO () Source #
rawSystemProgramStdout :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String Source #
rawSystemProgramConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO () Source #
rawSystemProgramStdoutConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO String Source #