Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Types / LocalBuildInfo.hs
blob116d5db264e8893d536ab864d987e7b77e242514
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE RankNTypes #-}
6 module Distribution.Types.LocalBuildInfo
7 ( -- * The type
8 LocalBuildInfo (..)
10 -- * Convenience accessors
11 , localComponentId
12 , localUnitId
13 , localCompatPackageKey
14 , localPackage
16 -- * Build targets of the 'LocalBuildInfo'.
17 , componentNameCLBIs
18 -- NB: the primes mean that they take a 'PackageDescription'
19 -- which may not match 'localPkgDescr' in 'LocalBuildInfo'.
20 -- More logical types would drop this argument, but
21 -- at the moment, this is the ONLY supported function, because
22 -- 'localPkgDescr' is not guaranteed to match. At some point
23 -- we will fix it and then we can use the (free) unprimed
24 -- namespace for the correct commands.
26 -- See https://github.com/haskell/cabal/issues/3606 for more
27 -- details.
29 , componentNameTargets'
30 , unitIdTarget'
31 , allTargetsInBuildOrder'
32 , withAllTargetsInBuildOrder'
33 , neededTargetsInBuildOrder'
34 , withNeededTargetsInBuildOrder'
35 , testCoverage
37 -- * Functions you SHOULD NOT USE (yet), but are defined here to
39 -- prevent someone from accidentally defining them
41 , componentNameTargets
42 , unitIdTarget
43 , allTargetsInBuildOrder
44 , withAllTargetsInBuildOrder
45 , neededTargetsInBuildOrder
46 , withNeededTargetsInBuildOrder
47 ) where
49 import Distribution.Compat.Prelude
50 import Prelude ()
52 import Distribution.Types.ComponentId
53 import Distribution.Types.ComponentLocalBuildInfo
54 import Distribution.Types.ComponentRequestedSpec
55 import Distribution.Types.PackageDescription
56 import Distribution.Types.PackageId
57 import Distribution.Types.TargetInfo
58 import Distribution.Types.UnitId
60 import Distribution.PackageDescription
61 import Distribution.Pretty
62 import Distribution.Simple.Compiler
63 import Distribution.Simple.InstallDirs hiding
64 ( absoluteInstallDirs
65 , prefixRelativeInstallDirs
66 , substPathTemplate
68 import Distribution.Simple.PackageIndex
69 import Distribution.Simple.Program
70 import Distribution.Simple.Setup.Config
71 import Distribution.System
73 import qualified Data.Map as Map
74 import Distribution.Compat.Graph (Graph)
75 import qualified Distribution.Compat.Graph as Graph
77 -- | Data cached after configuration step. See also
78 -- 'Distribution.Simple.Setup.ConfigFlags'.
79 data LocalBuildInfo = LocalBuildInfo
80 { configFlags :: ConfigFlags
81 -- ^ Options passed to the configuration step.
82 -- Needed to re-run configuration when .cabal is out of date
83 , flagAssignment :: FlagAssignment
84 -- ^ The final set of flags which were picked for this package
85 , componentEnabledSpec :: ComponentRequestedSpec
86 -- ^ What components were enabled during configuration, and why.
87 , extraConfigArgs :: [String]
88 -- ^ Extra args on the command line for the configuration step.
89 -- Needed to re-run configuration when .cabal is out of date
90 , installDirTemplates :: InstallDirTemplates
91 -- ^ The installation directories for the various different
92 -- kinds of files
93 -- TODO: inplaceDirTemplates :: InstallDirs FilePath
94 , compiler :: Compiler
95 -- ^ The compiler we're building with
96 , hostPlatform :: Platform
97 -- ^ The platform we're building for
98 , buildDir :: FilePath
99 -- ^ Where to build the package.
100 , cabalFilePath :: Maybe FilePath
101 -- ^ Path to the cabal file, if given during configuration.
102 , componentGraph :: Graph ComponentLocalBuildInfo
103 -- ^ All the components to build, ordered by topological
104 -- sort, and with their INTERNAL dependencies over the
105 -- intrapackage dependency graph.
106 -- TODO: this is assumed to be short; otherwise we want
107 -- some sort of ordered map.
108 , componentNameMap :: Map ComponentName [ComponentLocalBuildInfo]
109 -- ^ A map from component name to all matching
110 -- components. These coincide with 'componentGraph'
111 , promisedPkgs :: Map (PackageName, ComponentName) ComponentId
112 -- ^ The packages we were promised, but aren't already installed.
113 -- MP: Perhaps this just needs to be a Set UnitId at this stage.
114 , installedPkgs :: InstalledPackageIndex
115 -- ^ All the info about the installed packages that the
116 -- current package depends on (directly or indirectly).
117 -- The copy saved on disk does NOT include internal
118 -- dependencies (because we just don't have enough
119 -- information at this point to have an
120 -- 'InstalledPackageInfo' for an internal dep), but we
121 -- will often update it with the internal dependencies;
122 -- see for example 'Distribution.Simple.Build.build'.
123 -- (This admonition doesn't apply for per-component builds.)
124 , pkgDescrFile :: Maybe FilePath
125 -- ^ the filename containing the .cabal file, if available
126 , localPkgDescr :: PackageDescription
127 -- ^ WARNING WARNING WARNING Be VERY careful about using
128 -- this function; we haven't deprecated it but using it
129 -- could introduce subtle bugs related to
130 -- 'HookedBuildInfo'.
132 -- In principle, this is supposed to contain the
133 -- resolved package description, that does not contain
134 -- any conditionals. However, it MAY NOT contain
135 -- the description with a 'HookedBuildInfo' applied
136 -- to it; see 'HookedBuildInfo' for the whole sordid saga.
137 -- As much as possible, Cabal library should avoid using
138 -- this parameter.
139 , withPrograms :: ProgramDb
140 -- ^ Location and args for all programs
141 , withPackageDB :: PackageDBStack
142 -- ^ What package database to use, global\/user
143 , withVanillaLib :: Bool
144 -- ^ Whether to build normal libs.
145 , withProfLib :: Bool
146 -- ^ Whether to build profiling versions of libs.
147 , withSharedLib :: Bool
148 -- ^ Whether to build shared versions of libs.
149 , withStaticLib :: Bool
150 -- ^ Whether to build static versions of libs (with all other libs rolled in)
151 , withDynExe :: Bool
152 -- ^ Whether to link executables dynamically
153 , withFullyStaticExe :: Bool
154 -- ^ Whether to link executables fully statically
155 , withProfExe :: Bool
156 -- ^ Whether to build executables for profiling.
157 , withProfLibDetail :: ProfDetailLevel
158 -- ^ Level of automatic profile detail.
159 , withProfExeDetail :: ProfDetailLevel
160 -- ^ Level of automatic profile detail.
161 , withOptimization :: OptimisationLevel
162 -- ^ Whether to build with optimization (if available).
163 , withDebugInfo :: DebugInfoLevel
164 -- ^ Whether to emit debug info (if available).
165 , withGHCiLib :: Bool
166 -- ^ Whether to build libs suitable for use with GHCi.
167 , splitSections :: Bool
168 -- ^ Use -split-sections with GHC, if available
169 , splitObjs :: Bool
170 -- ^ Use -split-objs with GHC, if available
171 , stripExes :: Bool
172 -- ^ Whether to strip executables during install
173 , stripLibs :: Bool
174 -- ^ Whether to strip libraries during install
175 , exeCoverage :: Bool
176 -- ^ Whether to enable executable program coverage
177 , libCoverage :: Bool
178 -- ^ Whether to enable library program coverage
179 , progPrefix :: PathTemplate
180 -- ^ Prefix to be prepended to installed executables
181 , progSuffix :: PathTemplate
182 -- ^ Suffix to be appended to installed executables
183 , relocatable :: Bool -- ^Whether to build a relocatable package
185 deriving (Generic, Read, Show, Typeable)
187 instance Binary LocalBuildInfo
188 instance Structured LocalBuildInfo
190 -------------------------------------------------------------------------------
191 -- Accessor functions
193 -- TODO: Get rid of these functions, as much as possible. They are
194 -- a bit useful in some cases, but you should be very careful!
196 -- | Extract the 'ComponentId' from the public library component of a
197 -- 'LocalBuildInfo' if it exists, or make a fake component ID based
198 -- on the package ID.
199 localComponentId :: LocalBuildInfo -> ComponentId
200 localComponentId lbi =
201 case componentNameCLBIs lbi (CLibName LMainLibName) of
202 [LibComponentLocalBuildInfo{componentComponentId = cid}] ->
204 _ -> mkComponentId (prettyShow (localPackage lbi))
206 -- | Extract the 'PackageIdentifier' of a 'LocalBuildInfo'.
207 -- This is a "safe" use of 'localPkgDescr'
208 localPackage :: LocalBuildInfo -> PackageId
209 localPackage lbi = package (localPkgDescr lbi)
211 -- | Extract the 'UnitId' from the library component of a
212 -- 'LocalBuildInfo' if it exists, or make a fake unit ID based on
213 -- the package ID.
214 localUnitId :: LocalBuildInfo -> UnitId
215 localUnitId lbi =
216 case componentNameCLBIs lbi (CLibName LMainLibName) of
217 [LibComponentLocalBuildInfo{componentUnitId = uid}] ->
219 _ -> mkLegacyUnitId $ localPackage lbi
221 -- | Extract the compatibility package key from the public library component of a
222 -- 'LocalBuildInfo' if it exists, or make a fake package key based
223 -- on the package ID.
224 localCompatPackageKey :: LocalBuildInfo -> String
225 localCompatPackageKey lbi =
226 case componentNameCLBIs lbi (CLibName LMainLibName) of
227 [LibComponentLocalBuildInfo{componentCompatPackageKey = pk}] ->
229 _ -> prettyShow (localPackage lbi)
231 -- | Convenience function to generate a default 'TargetInfo' from a
232 -- 'ComponentLocalBuildInfo'. The idea is to call this once, and then
233 -- use 'TargetInfo' everywhere else. Private to this module.
234 mkTargetInfo :: PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> TargetInfo
235 mkTargetInfo pkg_descr _lbi clbi =
236 TargetInfo
237 { targetCLBI = clbi
238 , -- NB: @pkg_descr@, not @localPkgDescr lbi@!
239 targetComponent =
240 getComponent
241 pkg_descr
242 (componentLocalName clbi)
245 -- | Return all 'TargetInfo's associated with 'ComponentName'.
246 -- In the presence of Backpack there may be more than one!
247 -- Has a prime because it takes a 'PackageDescription' argument
248 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
249 componentNameTargets' :: PackageDescription -> LocalBuildInfo -> ComponentName -> [TargetInfo]
250 componentNameTargets' pkg_descr lbi cname =
251 case Map.lookup cname (componentNameMap lbi) of
252 Just clbis -> map (mkTargetInfo pkg_descr lbi) clbis
253 Nothing -> []
255 unitIdTarget' :: PackageDescription -> LocalBuildInfo -> UnitId -> Maybe TargetInfo
256 unitIdTarget' pkg_descr lbi uid =
257 case Graph.lookup uid (componentGraph lbi) of
258 Just clbi -> Just (mkTargetInfo pkg_descr lbi clbi)
259 Nothing -> Nothing
261 -- | Return all 'ComponentLocalBuildInfo's associated with 'ComponentName'.
262 -- In the presence of Backpack there may be more than one!
263 componentNameCLBIs :: LocalBuildInfo -> ComponentName -> [ComponentLocalBuildInfo]
264 componentNameCLBIs lbi cname =
265 case Map.lookup cname (componentNameMap lbi) of
266 Just clbis -> clbis
267 Nothing -> []
269 -- TODO: Maybe cache topsort (Graph can do this)
271 -- | Return the list of default 'TargetInfo's associated with a
272 -- configured package, in the order they need to be built.
273 -- Has a prime because it takes a 'PackageDescription' argument
274 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
275 allTargetsInBuildOrder' :: PackageDescription -> LocalBuildInfo -> [TargetInfo]
276 allTargetsInBuildOrder' pkg_descr lbi =
277 map (mkTargetInfo pkg_descr lbi) (Graph.revTopSort (componentGraph lbi))
279 -- | Execute @f@ for every 'TargetInfo' in the package, respecting the
280 -- build dependency order. (TODO: We should use Shake!)
281 -- Has a prime because it takes a 'PackageDescription' argument
282 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
283 withAllTargetsInBuildOrder' :: PackageDescription -> LocalBuildInfo -> (TargetInfo -> IO ()) -> IO ()
284 withAllTargetsInBuildOrder' pkg_descr lbi f =
285 sequence_ [f target | target <- allTargetsInBuildOrder' pkg_descr lbi]
287 -- | Return the list of all targets needed to build the @uids@, in
288 -- the order they need to be built.
289 -- Has a prime because it takes a 'PackageDescription' argument
290 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
291 neededTargetsInBuildOrder' :: PackageDescription -> LocalBuildInfo -> [UnitId] -> [TargetInfo]
292 neededTargetsInBuildOrder' pkg_descr lbi uids =
293 case Graph.closure (componentGraph lbi) uids of
294 Nothing -> error $ "localBuildPlan: missing uids " ++ intercalate ", " (map prettyShow uids)
295 Just clos -> map (mkTargetInfo pkg_descr lbi) (Graph.revTopSort (Graph.fromDistinctList clos))
297 -- | Execute @f@ for every 'TargetInfo' needed to build @uid@s, respecting
298 -- the build dependency order.
299 -- Has a prime because it takes a 'PackageDescription' argument
300 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
301 withNeededTargetsInBuildOrder' :: PackageDescription -> LocalBuildInfo -> [UnitId] -> (TargetInfo -> IO ()) -> IO ()
302 withNeededTargetsInBuildOrder' pkg_descr lbi uids f =
303 sequence_ [f target | target <- neededTargetsInBuildOrder' pkg_descr lbi uids]
305 -- | Is coverage enabled for test suites? In practice, this requires library
306 -- and executable profiling to be enabled.
307 testCoverage :: LocalBuildInfo -> Bool
308 testCoverage lbi = exeCoverage lbi && libCoverage lbi
310 -------------------------------------------------------------------------------
311 -- Stub functions to prevent someone from accidentally defining them
313 {-# WARNING componentNameTargets, unitIdTarget, allTargetsInBuildOrder, withAllTargetsInBuildOrder, neededTargetsInBuildOrder, withNeededTargetsInBuildOrder "By using this function, you may be introducing a bug where you retrieve a 'Component' which does not have 'HookedBuildInfo' applied to it. See the documentation for 'HookedBuildInfo' for an explanation of the issue. If you have a 'PackageDescription' handy (NOT from the 'LocalBuildInfo'), try using the primed version of the function, which takes it as an extra argument." #-}
314 componentNameTargets :: LocalBuildInfo -> ComponentName -> [TargetInfo]
315 componentNameTargets lbi = componentNameTargets' (localPkgDescr lbi) lbi
316 unitIdTarget :: LocalBuildInfo -> UnitId -> Maybe TargetInfo
317 unitIdTarget lbi = unitIdTarget' (localPkgDescr lbi) lbi
318 allTargetsInBuildOrder :: LocalBuildInfo -> [TargetInfo]
319 allTargetsInBuildOrder lbi = allTargetsInBuildOrder' (localPkgDescr lbi) lbi
320 withAllTargetsInBuildOrder :: LocalBuildInfo -> (TargetInfo -> IO ()) -> IO ()
321 withAllTargetsInBuildOrder lbi = withAllTargetsInBuildOrder' (localPkgDescr lbi) lbi
322 neededTargetsInBuildOrder :: LocalBuildInfo -> [UnitId] -> [TargetInfo]
323 neededTargetsInBuildOrder lbi = neededTargetsInBuildOrder' (localPkgDescr lbi) lbi
324 withNeededTargetsInBuildOrder :: LocalBuildInfo -> [UnitId] -> (TargetInfo -> IO ()) -> IO ()
325 withNeededTargetsInBuildOrder lbi = withNeededTargetsInBuildOrder' (localPkgDescr lbi) lbi