Cabal-3.0.1.0: A framework for packaging Haskell software

CopyrightIsaac Jones 2006 Duncan Coutts 2007-2009
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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 ProgramDb 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 ProgramDb would probably be a reader or state component of it.

The module also defines all the known built-in Programs and the defaultProgramDb 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.

Synopsis

Program and functions for constructing them

data Program Source #

Represents a program which can be configured.

Note: rather than constructing this directly, start with simpleProgram and override any extra fields.

Constructors

Program 

Fields

Instances
Show Program Source # 
Instance details

Defined in Distribution.Simple.Program.Types

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]

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

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.

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

  • programId :: String

    Just the name again

  • programVersion :: Maybe Version

    The version of this program, if it is known.

  • programDefaultArgs :: [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.

  • programOverrideArgs :: [String]

    Override command-line args for this program. These flags will appear last on the command line, so they override all earlier flags.

  • programOverrideEnv :: [(String, Maybe String)]

    Override environment variables for this program. These env vars will extend/override the prevailing environment of the current to form the environment for the new process.

  • programProperties :: Map String String

    A key-value map listing various properties of the program, useful for feature detection. Populated during the configuration step, key names depend on the specific program.

  • programLocation :: ProgramLocation

    Location of the program. eg. /usr/bin/ghc-6.4

  • programMonitorFiles :: [FilePath]

    In addition to the programLocation where the program was found, these are additional locations that were looked at. The combination of ths found location and these not-found locations can be used to monitor to detect when the re-configuring the program might give a different result (e.g. found in a different location).

Instances
Eq ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Read ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Show ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ConfiguredProgram :: Type -> Type #

Binary ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ConfiguredProgram Source # 
Instance details

Defined in Distribution.Simple.Program.Types

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

FoundOnSystem

The program was found automatically.

Instances
Eq ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Read ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Show ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ProgramLocation :: Type -> Type #

Binary ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramLocation Source # 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramLocation = D1 (MetaData "ProgramLocation" "Distribution.Simple.Program.Types" "Cabal-3.0.1.0-7bhPNuc4emeBQNpr9F8jJ" False) (C1 (MetaCons "UserSpecified" PrefixI True) (S1 (MetaSel (Just "locationPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: C1 (MetaCons "FoundOnSystem" PrefixI True) (S1 (MetaSel (Just "locationPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))

runProgram Source #

Arguments

:: Verbosity

Verbosity

-> ConfiguredProgram

The program to run

-> [ProgArg]

Any extra arguments to add

-> IO () 

Runs the given configured program.

getProgramOutput Source #

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.

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

data ProgramDb Source #

The configuration is a collection of information about programs. It contains information both about configured programs and also about programs that we are yet to configure.

The idea is that we start from a collection of unconfigured programs and one by one we try to configure them at which point we move them into the configured collection. For unconfigured programs we record not just the Program but also any user-provided arguments and location for the program.

Instances
Read ProgramDb Source #

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

Show ProgramDb Source #

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

Binary ProgramDb Source #

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

restoreProgramDb :: [Program] -> ProgramDb -> ProgramDb Source #

The 'Read'\/'Show' and Binary instances do not preserve all the unconfigured Programs because Program is not in 'Read'\/'Show' because it contains functions. So to fully restore a deserialised ProgramDb use this function to add back all the known Programs.

  • It does not add the default programs, but you probably want them, use builtinPrograms in addition to any extra you might need.

addKnownProgram :: Program -> ProgramDb -> ProgramDb Source #

Add a known program that we may configure later

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.

userSpecifyPath Source #

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.

userSpecifyArgs Source #

Arguments

:: String

Program 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 -> 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'.

needProgram :: Verbosity -> Program -> ProgramDb -> IO (Maybe (ConfiguredProgram, ProgramDb)) Source #

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

It returns Nothing if the program couldn't be configured, or is not found.

Since: 3.0.1.0

runDbProgram Source #

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.

getDbProgramOutput Source #

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