Correctly provision build tools in all situations
[cabal.git] / Cabal / src / Distribution / Simple / Program / Types.hs
blob630b22580cf1e48931eb43dbffb04fb79287dbfb
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE RankNTypes #-}
6 -----------------------------------------------------------------------------
8 -- |
9 -- Module : Distribution.Simple.Program.Types
10 -- Copyright : Isaac Jones 2006, Duncan Coutts 2007-2009
12 -- Maintainer : cabal-devel@haskell.org
13 -- Portability : portable
15 -- This provides an abstraction which deals with configuring and running
16 -- programs. A 'Program' is a static notion of a known program. A
17 -- 'ConfiguredProgram' is a 'Program' that has been found on the current
18 -- machine and is ready to be run (possibly with some user-supplied default
19 -- args). Configuring a program involves finding its location and if necessary
20 -- finding its version. There's reasonable default behavior for trying to find
21 -- \"foo\" in PATH, being able to override its location, etc.
22 module Distribution.Simple.Program.Types
23 ( -- * Program and functions for constructing them
24 Program (..)
25 , ProgramSearchPath
26 , ProgramSearchPathEntry (..)
28 -- * Configured program and related functions
29 , ConfiguredProgram (..)
30 , programPath
31 , suppressOverrideArgs
32 , ProgArg
33 , ProgramLocation (..)
34 , simpleConfiguredProgram
35 ) where
37 import Distribution.Compat.Prelude
38 import Prelude ()
40 import Distribution.PackageDescription
41 import Distribution.Verbosity
42 import Distribution.Version
44 import qualified Data.Map as Map
46 -- | Represents a program which can be configured.
48 -- Note: rather than constructing this directly, start with 'simpleProgram' and
49 -- override any extra fields.
50 data Program = Program
51 { programName :: String
52 -- ^ The simple name of the program, eg. ghc
53 , programFindLocation
54 :: Verbosity
55 -> ProgramSearchPath
56 -> IO (Maybe (FilePath, [FilePath]))
57 -- ^ A function to search for the program if its location was not
58 -- specified by the user. Usually this will just be a call to
59 -- 'findProgramOnSearchPath'.
61 -- It is supplied with the prevailing search path which will typically
62 -- just be used as-is, but can be extended or ignored as needed.
64 -- For the purpose of change monitoring, in addition to the location
65 -- where the program was found, it returns all the other places that
66 -- were tried.
67 , programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
68 -- ^ Try to find the version of the program. For many programs this is
69 -- not possible or is not necessary so it's OK to return Nothing.
70 , programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
71 -- ^ A function to do any additional configuration after we have
72 -- located the program (and perhaps identified its version). For example
73 -- it could add args, or environment vars.
74 , programNormaliseArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
75 -- ^ A function that filters any arguments that don't impact the output
76 -- from a commandline. Used to limit the volatility of dependency hashes
77 -- when using new-build.
80 instance Show Program where
81 show (Program name _ _ _ _) = "Program: " ++ name
83 type ProgArg = String
85 -- | A search path to use when locating executables. This is analogous
86 -- to the unix @$PATH@ or win32 @%PATH%@ but with the ability to use
87 -- the system default method for finding executables ('findExecutable' which
88 -- on unix is simply looking on the @$PATH@ but on win32 is a bit more
89 -- complicated).
91 -- The default to use is @[ProgSearchPathDefault]@ but you can add extra dirs
92 -- either before, after or instead of the default, e.g. here we add an extra
93 -- dir to search after the usual ones.
95 -- > ['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
97 -- We also use this path to set the environment when running child processes.
99 -- The @ProgramDb@ is created with a @ProgramSearchPath@ to which we
100 -- @prependProgramSearchPath@ to add the ones that come from cli flags and from
101 -- configurations. Then each of the programs that are configured in the db
102 -- inherits the same path as part of @configureProgram@.
103 type ProgramSearchPath = [ProgramSearchPathEntry]
105 data ProgramSearchPathEntry
106 = -- | A specific dir
107 ProgramSearchPathDir FilePath
108 | -- | The system default
109 ProgramSearchPathDefault
110 deriving (Show, Eq, Generic, Typeable)
112 instance Binary ProgramSearchPathEntry
113 instance Structured ProgramSearchPathEntry
115 -- | Represents a program which has been configured and is thus ready to be run.
117 -- These are usually made by configuring a 'Program', but if you have to
118 -- construct one directly then start with 'simpleConfiguredProgram' and
119 -- override any extra fields.
120 data ConfiguredProgram = ConfiguredProgram
121 { programId :: String
122 -- ^ Just the name again
123 , programVersion :: Maybe Version
124 -- ^ The version of this program, if it is known.
125 , programDefaultArgs :: [String]
126 -- ^ Default command-line args for this program.
127 -- These flags will appear first on the command line, so they can be
128 -- overridden by subsequent flags.
129 , programOverrideArgs :: [String]
130 -- ^ Override command-line args for this program.
131 -- These flags will appear last on the command line, so they override
132 -- all earlier flags.
133 , programOverrideEnv :: [(String, Maybe String)]
134 -- ^ Override environment variables for this program.
135 -- These env vars will extend\/override the prevailing environment of
136 -- the current to form the environment for the new process.
137 , programProperties :: Map.Map String String
138 -- ^ A key-value map listing various properties of the program, useful
139 -- for feature detection. Populated during the configuration step, key
140 -- names depend on the specific program.
141 , programLocation :: ProgramLocation
142 -- ^ Location of the program. eg. @\/usr\/bin\/ghc-6.4@
143 , programMonitorFiles :: [FilePath]
144 -- ^ In addition to the 'programLocation' where the program was found,
145 -- these are additional locations that were looked at. The combination
146 -- of ths found location and these not-found locations can be used to
147 -- monitor to detect when the re-configuring the program might give a
148 -- different result (e.g. found in a different location).
150 deriving (Eq, Generic, Read, Show, Typeable)
152 instance Binary ConfiguredProgram
153 instance Structured ConfiguredProgram
155 -- | Where a program was found. Also tells us whether it's specified by user or
156 -- not. This includes not just the path, but the program as well.
157 data ProgramLocation
158 = -- | The user gave the path to this program,
159 -- eg. --ghc-path=\/usr\/bin\/ghc-6.6
160 UserSpecified {locationPath :: FilePath}
161 | -- | The program was found automatically.
162 FoundOnSystem {locationPath :: FilePath}
163 deriving (Eq, Generic, Read, Show, Typeable)
165 instance Binary ProgramLocation
166 instance Structured ProgramLocation
168 -- | The full path of a configured program.
169 programPath :: ConfiguredProgram -> FilePath
170 programPath = locationPath . programLocation
172 -- | Suppress any extra arguments added by the user.
173 suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram
174 suppressOverrideArgs prog = prog{programOverrideArgs = []}
176 -- | Make a simple 'ConfiguredProgram'.
178 -- > simpleConfiguredProgram "foo" (FoundOnSystem path)
179 simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
180 simpleConfiguredProgram name loc =
181 ConfiguredProgram
182 { programId = name
183 , programVersion = Nothing
184 , programDefaultArgs = []
185 , programOverrideArgs = []
186 , programOverrideEnv = []
187 , programProperties = Map.empty
188 , programLocation = loc
189 , programMonitorFiles = [] -- did not look in any other locations