Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / LocalBuildInfo.hs
blob8659764d0c4c02174b29b7156aaa83278f7f450a
1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE DuplicateRecordFields #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE NamedFieldPuns #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.LocalBuildInfo
11 -- Copyright : Isaac Jones 2003-2004
12 -- License : BSD3
14 -- Maintainer : cabal-devel@haskell.org
15 -- Portability : portable
17 -- Once a package has been configured we have resolved conditionals and
18 -- dependencies, configured the compiler and other needed external programs.
19 -- The 'LocalBuildInfo' is used to hold all this information. It holds the
20 -- install dirs, the compiler, the exact package dependencies, the configured
21 -- programs, the package database to use and a bunch of miscellaneous configure
22 -- flags. It gets saved and reloaded from a file (@dist\/setup-config@). It gets
23 -- passed in to very many subsequent build actions.
24 module Distribution.Simple.LocalBuildInfo
25 ( LocalBuildInfo (..)
26 , localComponentId
27 , localUnitId
28 , localCompatPackageKey
30 -- * Convenience accessors
31 , buildDir
32 , cabalFilePath
33 , progPrefix
34 , progSuffix
36 -- * Buildable package components
37 , Component (..)
38 , ComponentName (..)
39 , LibraryName (..)
40 , defaultLibName
41 , showComponentName
42 , componentNameString
43 , ComponentLocalBuildInfo (..)
44 , componentBuildDir
45 , foldComponent
46 , componentName
47 , componentBuildInfo
48 , componentBuildable
49 , pkgComponents
50 , pkgBuildableComponents
51 , lookupComponent
52 , getComponent
53 , allComponentsInBuildOrder
54 , depLibraryPaths
55 , allLibModules
56 , withAllComponentsInBuildOrder
57 , withLibLBI
58 , withExeLBI
59 , withBenchLBI
60 , withTestLBI
61 , enabledTestLBIs
62 , enabledBenchLBIs
64 -- * Installation directories
65 , module Distribution.Simple.InstallDirs
66 , absoluteInstallDirs
67 , prefixRelativeInstallDirs
68 , absoluteInstallCommandDirs
69 , absoluteComponentInstallDirs
70 , prefixRelativeComponentInstallDirs
71 , substPathTemplate
72 ) where
74 import Distribution.Compat.Prelude
75 import Prelude ()
77 import Distribution.Types.Component
78 import Distribution.Types.ComponentLocalBuildInfo
79 import Distribution.Types.ComponentName
80 import Distribution.Types.LocalBuildInfo
81 import Distribution.Types.PackageDescription
82 import Distribution.Types.PackageId
83 import Distribution.Types.TargetInfo
84 import Distribution.Types.UnitId
85 import Distribution.Types.UnqualComponentName
87 import qualified Distribution.Compat.Graph as Graph
88 import qualified Distribution.InstalledPackageInfo as Installed
89 import Distribution.ModuleName
90 import Distribution.Package
91 import Distribution.PackageDescription
92 import Distribution.Pretty
93 import Distribution.Simple.Compiler
94 import Distribution.Simple.InstallDirs hiding
95 ( absoluteInstallDirs
96 , prefixRelativeInstallDirs
97 , substPathTemplate
99 import qualified Distribution.Simple.InstallDirs as InstallDirs
100 import Distribution.Simple.PackageIndex
101 import Distribution.Simple.Utils
103 import Data.List (stripPrefix)
104 import System.FilePath
106 import System.Directory (canonicalizePath, doesDirectoryExist)
108 -- -----------------------------------------------------------------------------
109 -- Configuration information of buildable components
111 componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
112 -- For now, we assume that libraries/executables/test-suites/benchmarks
113 -- are only ever built once. With Backpack, we need a special case for
114 -- libraries so that we can handle building them multiple times.
115 componentBuildDir lbi clbi =
116 buildDir lbi
117 </> case componentLocalName clbi of
118 CLibName LMainLibName ->
119 if prettyShow (componentUnitId clbi) == prettyShow (componentComponentId clbi)
120 then ""
121 else prettyShow (componentUnitId clbi)
122 CLibName (LSubLibName s) ->
123 if prettyShow (componentUnitId clbi) == prettyShow (componentComponentId clbi)
124 then unUnqualComponentName s
125 else prettyShow (componentUnitId clbi)
126 CFLibName s -> unUnqualComponentName s
127 CExeName s -> unUnqualComponentName s
128 CTestName s -> unUnqualComponentName s
129 CBenchName s -> unUnqualComponentName s
131 -- | Perform the action on each enabled 'library' in the package
132 -- description with the 'ComponentLocalBuildInfo'.
133 withLibLBI
134 :: PackageDescription
135 -> LocalBuildInfo
136 -> (Library -> ComponentLocalBuildInfo -> IO ())
137 -> IO ()
138 withLibLBI pkg lbi f =
139 withAllTargetsInBuildOrder' pkg lbi $ \target ->
140 case targetComponent target of
141 CLib lib -> f lib (targetCLBI target)
142 _ -> return ()
144 -- | Perform the action on each enabled 'Executable' in the package
145 -- description. Extended version of 'withExe' that also gives corresponding
146 -- build info.
147 withExeLBI
148 :: PackageDescription
149 -> LocalBuildInfo
150 -> (Executable -> ComponentLocalBuildInfo -> IO ())
151 -> IO ()
152 withExeLBI pkg lbi f =
153 withAllTargetsInBuildOrder' pkg lbi $ \target ->
154 case targetComponent target of
155 CExe exe -> f exe (targetCLBI target)
156 _ -> return ()
158 -- | Perform the action on each enabled 'Benchmark' in the package
159 -- description.
160 withBenchLBI
161 :: PackageDescription
162 -> LocalBuildInfo
163 -> (Benchmark -> ComponentLocalBuildInfo -> IO ())
164 -> IO ()
165 withBenchLBI pkg lbi f =
166 sequence_ [f bench clbi | (bench, clbi) <- enabledBenchLBIs pkg lbi]
168 withTestLBI
169 :: PackageDescription
170 -> LocalBuildInfo
171 -> (TestSuite -> ComponentLocalBuildInfo -> IO ())
172 -> IO ()
173 withTestLBI pkg lbi f =
174 sequence_ [f test clbi | (test, clbi) <- enabledTestLBIs pkg lbi]
176 enabledTestLBIs
177 :: PackageDescription
178 -> LocalBuildInfo
179 -> [(TestSuite, ComponentLocalBuildInfo)]
180 enabledTestLBIs pkg lbi =
181 [ (test, targetCLBI target)
182 | target <- allTargetsInBuildOrder' pkg lbi
183 , CTest test <- [targetComponent target]
186 enabledBenchLBIs
187 :: PackageDescription
188 -> LocalBuildInfo
189 -> [(Benchmark, ComponentLocalBuildInfo)]
190 enabledBenchLBIs pkg lbi =
191 [ (bench, targetCLBI target)
192 | target <- allTargetsInBuildOrder' pkg lbi
193 , CBench bench <- [targetComponent target]
196 -- | Perform the action on each buildable 'Library' or 'Executable' (Component)
197 -- in the PackageDescription, subject to the build order specified by the
198 -- 'compBuildOrder' field of the given 'LocalBuildInfo'
199 withAllComponentsInBuildOrder
200 :: PackageDescription
201 -> LocalBuildInfo
202 -> (Component -> ComponentLocalBuildInfo -> IO ())
203 -> IO ()
204 withAllComponentsInBuildOrder pkg lbi f =
205 withAllTargetsInBuildOrder' pkg lbi $ \target ->
206 f (targetComponent target) (targetCLBI target)
208 allComponentsInBuildOrder
209 :: LocalBuildInfo
210 -> [ComponentLocalBuildInfo]
211 allComponentsInBuildOrder (LocalBuildInfo{componentGraph = compGraph}) =
212 Graph.topSort compGraph
214 -- -----------------------------------------------------------------------------
215 -- A random function that has no business in this module
217 -- | Determine the directories containing the dynamic libraries of the
218 -- transitive dependencies of the component we are building.
220 -- When wanted, and possible, returns paths relative to the installDirs 'prefix'
221 depLibraryPaths
222 :: Bool
223 -- ^ Building for inplace?
224 -> Bool
225 -- ^ Generate prefix-relative library paths
226 -> LocalBuildInfo
227 -> ComponentLocalBuildInfo
228 -- ^ Component that is being built
229 -> IO [FilePath]
230 depLibraryPaths
231 inplace
232 relative
233 lbi@( LocalBuildInfo
234 { localPkgDescr = pkgDescr
235 , installedPkgs = installed
238 clbi = do
239 let installDirs = absoluteComponentInstallDirs pkgDescr lbi (componentUnitId clbi) NoCopyDest
240 executable = case clbi of
241 ExeComponentLocalBuildInfo{} -> True
242 _ -> False
243 relDir
244 | executable = bindir installDirs
245 | otherwise = libdir installDirs
248 -- TODO: this is kind of inefficient
249 internalDeps =
250 [ uid
251 | (uid, _) <- componentPackageDeps clbi
252 , -- Test that it's internal
253 sub_target <- allTargetsInBuildOrder' pkgDescr lbi
254 , componentUnitId (targetCLBI (sub_target)) == uid
256 internalLibs =
257 [ getLibDir (targetCLBI sub_target)
258 | sub_target <-
259 neededTargetsInBuildOrder'
260 pkgDescr
262 internalDeps
265 -- This is better, but it doesn't work, because we may be passed a
266 -- CLBI which doesn't actually exist, and was faked up when we
267 -- were building a test suite/benchmark. See #3599 for proposal
268 -- to fix this.
269 let internalCLBIs = filter ((/= componentUnitId clbi) . componentUnitId)
270 . map targetCLBI
271 $ neededTargetsInBuildOrder lbi [componentUnitId clbi]
272 internalLibs = map getLibDir internalCLBIs
274 getLibDir sub_clbi
275 | inplace = componentBuildDir lbi sub_clbi
276 | otherwise = dynlibdir (absoluteComponentInstallDirs pkgDescr lbi (componentUnitId sub_clbi) NoCopyDest)
278 -- Why do we go through all the trouble of a hand-crafting
279 -- internalLibs, when 'installedPkgs' actually contains the
280 -- internal libraries? The trouble is that 'installedPkgs'
281 -- may contain *inplace* entries, which we must NOT use for
282 -- not inplace 'depLibraryPaths' (e.g., for RPATH calculation).
283 -- See #4025 for more details. This is all horrible but it
284 -- is a moot point if you are using a per-component build,
285 -- because you never have any internal libraries in this case;
286 -- they're all external.
287 let external_ipkgs = filter is_external (allPackages installed)
288 is_external ipkg = not (installedUnitId ipkg `elem` internalDeps)
289 -- First look for dynamic libraries in `dynamic-library-dirs`, and use
290 -- `library-dirs` as a fall back.
291 getDynDir pkg = case Installed.libraryDynDirs pkg of
292 [] -> Installed.libraryDirs pkg
293 d -> d
294 allDepLibDirs = concatMap getDynDir external_ipkgs
296 allDepLibDirs' = internalLibs ++ allDepLibDirs
297 allDepLibDirsC <- traverse canonicalizePathNoFail allDepLibDirs'
299 let p = prefix installDirs
300 prefixRelative l = isJust (stripPrefix p l)
301 libPaths
302 | relative
303 && prefixRelative relDir =
305 ( \l ->
306 if prefixRelative l
307 then shortRelativePath relDir l
308 else l
310 allDepLibDirsC
311 | otherwise = allDepLibDirsC
313 -- For some reason, this function returns lots of duplicates. Avoid
314 -- exceeding `ARG_MAX` (the result of this function is used to populate
315 -- `LD_LIBRARY_PATH`) by deduplicating the list.
316 return $ ordNub libPaths
317 where
318 -- 'canonicalizePath' fails on UNIX when the directory does not exists.
319 -- So just don't canonicalize when it doesn't exist.
320 canonicalizePathNoFail p = do
321 exists <- doesDirectoryExist p
322 if exists
323 then canonicalizePath p
324 else return p
326 -- | Get all module names that needed to be built by GHC; i.e., all
327 -- of these 'ModuleName's have interface files associated with them
328 -- that need to be installed.
329 allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName]
330 allLibModules lib clbi =
331 ordNub $
332 explicitLibModules lib
333 ++ case clbi of
334 LibComponentLocalBuildInfo{componentInstantiatedWith = insts} -> map fst insts
335 _ -> []
337 -- -----------------------------------------------------------------------------
338 -- Wrappers for a couple functions from InstallDirs
340 -- | Backwards compatibility function which computes the InstallDirs
341 -- assuming that @$libname@ points to the public library (or some fake
342 -- package identifier if there is no public library.) IF AT ALL
343 -- POSSIBLE, please use 'absoluteComponentInstallDirs' instead.
344 absoluteInstallDirs
345 :: PackageDescription
346 -> LocalBuildInfo
347 -> CopyDest
348 -> InstallDirs FilePath
349 absoluteInstallDirs pkg lbi copydest =
350 absoluteComponentInstallDirs pkg lbi (localUnitId lbi) copydest
352 -- | See 'InstallDirs.absoluteInstallDirs'.
353 absoluteComponentInstallDirs
354 :: PackageDescription
355 -> LocalBuildInfo
356 -> UnitId
357 -> CopyDest
358 -> InstallDirs FilePath
359 absoluteComponentInstallDirs
361 (LocalBuildInfo{compiler = comp, hostPlatform = plat, installDirTemplates = installDirs})
363 copydest =
364 InstallDirs.absoluteInstallDirs
365 (packageId pkg)
367 (compilerInfo comp)
368 copydest
369 plat
370 installDirs
372 absoluteInstallCommandDirs
373 :: PackageDescription
374 -> LocalBuildInfo
375 -> UnitId
376 -> CopyDest
377 -> InstallDirs FilePath
378 absoluteInstallCommandDirs pkg lbi uid copydest =
379 dirs
380 { -- Handle files which are not
381 -- per-component (data files and Haddock files.)
382 datadir = datadir dirs'
383 , -- NB: The situation with Haddock is a bit delicate. On the
384 -- one hand, the easiest to understand Haddock documentation
385 -- path is pkgname-0.1, which means it's per-package (not
386 -- per-component). But this means that it's impossible to
387 -- install Haddock documentation for internal libraries. We'll
388 -- keep this constraint for now; this means you can't use
389 -- Cabal to Haddock internal libraries. This does not seem
390 -- like a big problem.
391 docdir = docdir dirs'
392 , htmldir = htmldir dirs'
393 , haddockdir = haddockdir dirs'
395 where
396 dirs = absoluteComponentInstallDirs pkg lbi uid copydest
397 -- Notice use of 'absoluteInstallDirs' (not the
398 -- per-component variant). This means for non-library
399 -- packages we'll just pick a nondescriptive foo-0.1
400 dirs' = absoluteInstallDirs pkg lbi copydest
402 -- | Backwards compatibility function which computes the InstallDirs
403 -- assuming that @$libname@ points to the public library (or some fake
404 -- package identifier if there is no public library.) IF AT ALL
405 -- POSSIBLE, please use 'prefixRelativeComponentInstallDirs' instead.
406 prefixRelativeInstallDirs
407 :: PackageId
408 -> LocalBuildInfo
409 -> InstallDirs (Maybe FilePath)
410 prefixRelativeInstallDirs pkg_descr lbi =
411 prefixRelativeComponentInstallDirs pkg_descr lbi (localUnitId lbi)
413 -- | See 'InstallDirs.prefixRelativeInstallDirs'
414 prefixRelativeComponentInstallDirs
415 :: PackageId
416 -> LocalBuildInfo
417 -> UnitId
418 -> InstallDirs (Maybe FilePath)
419 prefixRelativeComponentInstallDirs
420 pkg_descr
421 (LocalBuildInfo{compiler = comp, hostPlatform = plat, installDirTemplates = installDirs})
422 uid =
423 InstallDirs.prefixRelativeInstallDirs
424 (packageId pkg_descr)
426 (compilerInfo comp)
427 plat
428 installDirs
430 substPathTemplate
431 :: PackageId
432 -> LocalBuildInfo
433 -> UnitId
434 -> PathTemplate
435 -> FilePath
436 substPathTemplate
437 pkgid
438 (LocalBuildInfo{compiler = comp, hostPlatform = plat})
439 uid =
440 fromPathTemplate
441 . (InstallDirs.substPathTemplate env)
442 where
443 env =
444 initialPathTemplateEnv
445 pkgid
447 (compilerInfo comp)
448 plat