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