Cabal-3.11.0.0: A framework for packaging Haskell software
CopyrightDuncan Coutts 2013
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple.Program.Find

Description

A somewhat extended notion of the normal program search path concept.

Usually when finding executables we just want to look in the usual places using the OS's usual method for doing so. In Haskell the normal OS-specific method is captured by findExecutable. On all common OSs that makes use of a PATH environment variable, (though on Windows it is not just the PATH).

However it is sometimes useful to be able to look in additional locations without having to change the process-global PATH environment variable. So we need an extension of the usual findExecutable that can look in additional locations, either before, after or instead of the normal OS locations.

Synopsis

Program search path

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 appendProgramSearchPath 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 #

Constructors

ProgramSearchPathDir FilePath

A specific dir

ProgramSearchPathDefault

The system default

Instances

Instances details
Structured ProgramSearchPathEntry Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Binary ProgramSearchPathEntry Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ProgramSearchPathEntry Source # 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ProgramSearchPathEntry 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramSearchPathEntry = D1 ('MetaData "ProgramSearchPathEntry" "Distribution.Simple.Program.Types" "Cabal-3.11.0.0-inplace" 'False) (C1 ('MetaCons "ProgramSearchPathDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "ProgramSearchPathDefault" 'PrefixI 'False) (U1 :: Type -> Type))
Eq ProgramSearchPathEntry Source # 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramSearchPathEntry Source # 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramSearchPathEntry = D1 ('MetaData "ProgramSearchPathEntry" "Distribution.Simple.Program.Types" "Cabal-3.11.0.0-inplace" 'False) (C1 ('MetaCons "ProgramSearchPathDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "ProgramSearchPathDefault" 'PrefixI 'False) (U1 :: Type -> Type))

programSearchPathAsPATHVar :: ProgramSearchPath -> IO String Source #

Interpret a ProgramSearchPath to construct a new $PATH env var. Note that this is close but not perfect because on Windows the search algorithm looks at more than just the %PATH%.

getSystemSearchPath :: IO [FilePath] Source #

Get the system search path. On Unix systems this is just the $PATH env var, but on windows it's a bit more complicated.

getExtraPathEnv :: Verbosity -> [(String, Maybe String)] -> [FilePath] -> IO [(String, Maybe String)] Source #

Adds some paths to the PATH entry in the key-value environment provided or if there is none, looks up $PATH in the real environment.

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