Copyright | Isaac Jones 2006 Duncan Coutts 2007-2009 |
---|---|
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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's reasonable default behavior for trying to find
"foo" in PATH, being able to override its location, etc.
Synopsis
- data Program = Program {
- programName :: String
- programFindLocation :: Verbosity -> ProgramSearchPath -> IO (Maybe (FilePath, [FilePath]))
- programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
- programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
- programNormaliseArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
- type ProgramSearchPath = [ProgramSearchPathEntry]
- data ProgramSearchPathEntry
- data ConfiguredProgram = ConfiguredProgram {}
- programPath :: ConfiguredProgram -> FilePath
- suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram
- type ProgArg = String
- data ProgramLocation
- = UserSpecified { }
- | FoundOnSystem { }
- simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
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.
Program | |
|
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]
We also use this path to set the environment when running child processes.
The ProgramDb
is created with a ProgramSearchPath
to which we
prependProgramSearchPath
to add the ones that come from cli flags and from
configurations. Then each of the programs that are configured in the db
inherits the same path as part of configureProgram
.
data ProgramSearchPathEntry Source #
ProgramSearchPathDir FilePath | A specific dir |
ProgramSearchPathDefault | The system default |
Instances
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.
ConfiguredProgram | |
|
Instances
Structured ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types structure :: Proxy ConfiguredProgram -> Structure Source # structureHash' :: Tagged ConfiguredProgram MD5 | |||||
Binary ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types put :: ConfiguredProgram -> Put # get :: Get ConfiguredProgram # putList :: [ConfiguredProgram] -> Put # | |||||
Generic ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types
from :: ConfiguredProgram -> Rep ConfiguredProgram x # to :: Rep ConfiguredProgram x -> ConfiguredProgram # | |||||
Read ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types | |||||
Show ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types showsPrec :: Int -> ConfiguredProgram -> ShowS # show :: ConfiguredProgram -> String # showList :: [ConfiguredProgram] -> ShowS # | |||||
Eq ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types (==) :: ConfiguredProgram -> ConfiguredProgram -> Bool # (/=) :: ConfiguredProgram -> ConfiguredProgram -> Bool # | |||||
type Rep ConfiguredProgram Source # | |||||
Defined in Distribution.Simple.Program.Types type Rep ConfiguredProgram = D1 ('MetaData "ConfiguredProgram" "Distribution.Simple.Program.Types" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "ConfiguredProgram" 'PrefixI 'True) (((S1 ('MetaSel ('Just "programId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "programVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :*: (S1 ('MetaSel ('Just "programDefaultArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "programOverrideArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "programOverrideEnv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Maybe String)]) :*: S1 ('MetaSel ('Just "programProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))) :*: (S1 ('MetaSel ('Just "programLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramLocation) :*: S1 ('MetaSel ('Just "programMonitorFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))))) |
programPath :: ConfiguredProgram -> FilePath Source #
The full path of a configured program.
suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram Source #
Suppress any extra arguments added by the user.
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.
UserSpecified | The user gave the path to this program, eg. --ghc-path=/usr/bin/ghc-6.6 |
FoundOnSystem | The program was found automatically. |
Instances
Structured ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types structure :: Proxy ProgramLocation -> Structure Source # structureHash' :: Tagged ProgramLocation MD5 | |||||
Binary ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types | |||||
Generic ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types
from :: ProgramLocation -> Rep ProgramLocation x # to :: Rep ProgramLocation x -> ProgramLocation # | |||||
Read ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types | |||||
Show ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types showsPrec :: Int -> ProgramLocation -> ShowS # show :: ProgramLocation -> String # showList :: [ProgramLocation] -> ShowS # | |||||
Eq ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types (==) :: ProgramLocation -> ProgramLocation -> Bool # (/=) :: ProgramLocation -> ProgramLocation -> Bool # | |||||
type Rep ProgramLocation Source # | |||||
Defined in Distribution.Simple.Program.Types type Rep ProgramLocation = D1 ('MetaData "ProgramLocation" "Distribution.Simple.Program.Types" "Cabal-3.14.0.0-be97" '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))) |
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram Source #
Make a simple ConfiguredProgram
.
simpleConfiguredProgram "foo" (FoundOnSystem path)