make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / Types / PackageDescription.hs
blob5e64694ac1f686f70e62620b0126e8786a86c0e3
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Types.PackageDescription
11 -- Copyright : Isaac Jones 2003-2005
12 -- License : BSD3
14 -- Maintainer : cabal-devel@haskell.org
15 -- Portability : portable
17 -- This defines the data structure for the @.cabal@ file format. There are
18 -- several parts to this structure. It has top level info and then 'Library',
19 -- 'Executable', 'TestSuite', and 'Benchmark' sections each of which have
20 -- associated 'BuildInfo' data that's used to build the library, exe, test, or
21 -- benchmark. To further complicate things there is both a 'PackageDescription'
22 -- and a 'GenericPackageDescription'. This distinction relates to cabal
23 -- configurations. When we initially read a @.cabal@ file we get a
24 -- 'GenericPackageDescription' which has all the conditional sections.
25 -- Before actually building a package we have to decide
26 -- on each conditional. Once we've done that we get a 'PackageDescription'.
27 -- It was done this way initially to avoid breaking too much stuff when the
28 -- feature was introduced. It could probably do with being rationalised at some
29 -- point to make it simpler.
30 module Distribution.Types.PackageDescription
31 ( PackageDescription (..)
32 , license
33 , license'
34 , buildType
35 , emptyPackageDescription
36 , hasPublicLib
37 , hasLibs
38 , allLibraries
39 , withLib
40 , hasExes
41 , withExe
42 , hasTests
43 , withTest
44 , hasBenchmarks
45 , withBenchmark
46 , hasForeignLibs
47 , withForeignLib
48 , allBuildInfo
49 , enabledBuildInfos
50 , allBuildDepends
51 , enabledBuildDepends
52 , updatePackageDescription
53 , pkgComponents
54 , pkgBuildableComponents
55 , enabledComponents
56 , lookupComponent
57 , getComponent
58 ) where
60 import Distribution.Compat.Prelude
61 import Prelude ()
63 import Control.Monad ((<=<))
65 -- lens
67 import Distribution.Types.Benchmark
68 import qualified Distribution.Types.BuildInfo.Lens as L
69 import Distribution.Types.Executable
70 import Distribution.Types.ForeignLib
71 import Distribution.Types.Library
72 import Distribution.Types.TestSuite
74 import Distribution.Types.BuildInfo
75 import Distribution.Types.BuildType
76 import Distribution.Types.Component
77 import Distribution.Types.ComponentName
78 import Distribution.Types.ComponentRequestedSpec
79 import Distribution.Types.Dependency
80 import Distribution.Types.HookedBuildInfo
81 import Distribution.Types.PackageId
82 import Distribution.Types.PackageName
83 import Distribution.Types.SetupBuildInfo
84 import Distribution.Types.SourceRepo
85 import Distribution.Types.UnqualComponentName
87 import Distribution.CabalSpecVersion
88 import Distribution.Compiler
89 import Distribution.License
90 import Distribution.Package
91 import Distribution.Utils.Path
92 import Distribution.Utils.ShortText
93 import Distribution.Version
95 import qualified Distribution.SPDX as SPDX
97 -- -----------------------------------------------------------------------------
98 -- The PackageDescription type
100 -- | This data type is the internal representation of the file @pkg.cabal@.
101 -- It contains two kinds of information about the package: information
102 -- which is needed for all packages, such as the package name and version, and
103 -- information which is needed for the simple build system only, such as
104 -- the compiler options and library name.
105 data PackageDescription = PackageDescription
106 { -- the following are required by all packages:
108 specVersion :: CabalSpecVersion
109 -- ^ The version of the Cabal spec that this package description uses.
110 , package :: PackageIdentifier
111 , licenseRaw :: Either SPDX.License License
112 , licenseFiles :: [RelativePath Pkg File]
113 , copyright :: !ShortText
114 , maintainer :: !ShortText
115 , author :: !ShortText
116 , stability :: !ShortText
117 , testedWith :: [(CompilerFlavor, VersionRange)]
118 , homepage :: !ShortText
119 , pkgUrl :: !ShortText
120 , bugReports :: !ShortText
121 , sourceRepos :: [SourceRepo]
122 , synopsis :: !ShortText
123 -- ^ A one-line summary of this package
124 , description :: !ShortText
125 -- ^ A more verbose description of this package
126 , category :: !ShortText
127 , customFieldsPD :: [(String, String)]
128 -- ^ Custom fields starting
129 -- with x-, stored in a
130 -- simple assoc-list.
131 , buildTypeRaw :: Maybe BuildType
132 -- ^ The original @build-type@ value as parsed from the
133 -- @.cabal@ file without defaulting. See also 'buildType'.
135 -- @since 2.2
136 , setupBuildInfo :: Maybe SetupBuildInfo
137 , -- components
138 library :: Maybe Library
139 , subLibraries :: [Library]
140 , executables :: [Executable]
141 , foreignLibs :: [ForeignLib]
142 , testSuites :: [TestSuite]
143 , benchmarks :: [Benchmark]
144 , -- files
145 dataFiles :: [RelativePath DataDir File]
146 -- ^ data file globs, relative to data directory
147 , dataDir :: SymbolicPath Pkg (Dir DataDir)
148 -- ^ data directory (may be absolute, or relative to package)
149 , extraSrcFiles :: [RelativePath Pkg File]
150 , extraTmpFiles :: [RelativePath Pkg File]
151 , extraDocFiles :: [RelativePath Pkg File]
152 , extraFiles :: [RelativePath Pkg File]
154 deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
156 instance Binary PackageDescription
157 instance Structured PackageDescription
159 instance NFData PackageDescription where rnf = genericRnf
161 instance Package PackageDescription where
162 packageId = package
164 -- | The SPDX 'LicenseExpression' of the package.
166 -- @since 2.2.0.0
167 license :: PackageDescription -> SPDX.License
168 license = license' . licenseRaw
170 -- | See 'license'.
172 -- @since 2.2.0.0
173 license' :: Either SPDX.License License -> SPDX.License
174 license' = either id licenseToSPDX
176 -- | The effective @build-type@ after applying defaulting rules.
178 -- The original @build-type@ value parsed is stored in the
179 -- 'buildTypeRaw' field. However, the @build-type@ field is optional
180 -- and can therefore be empty in which case we need to compute the
181 -- /effective/ @build-type@. This function implements the following
182 -- defaulting rules:
184 -- * For @cabal-version:2.0@ and below, default to the @Custom@
185 -- build-type unconditionally.
187 -- * Otherwise, if a @custom-setup@ stanza is defined, default to
188 -- the @Custom@ build-type; else default to @Simple@ build-type.
190 -- @since 2.2
191 buildType :: PackageDescription -> BuildType
192 buildType pkg
193 | specVersion pkg >= CabalSpecV2_2 =
194 fromMaybe newDefault (buildTypeRaw pkg)
195 | otherwise -- cabal-version < 2.1
197 fromMaybe Custom (buildTypeRaw pkg)
198 where
199 newDefault
200 | isNothing (setupBuildInfo pkg) = Simple
201 | otherwise = Custom
203 emptyPackageDescription :: PackageDescription
204 emptyPackageDescription =
205 PackageDescription
206 { package =
207 PackageIdentifier
208 (mkPackageName "")
209 nullVersion
210 , licenseRaw = Right UnspecifiedLicense -- TODO:
211 , licenseFiles = []
212 , specVersion = CabalSpecV1_0
213 , buildTypeRaw = Nothing
214 , copyright = mempty
215 , maintainer = mempty
216 , author = mempty
217 , stability = mempty
218 , testedWith = []
219 , homepage = mempty
220 , pkgUrl = mempty
221 , bugReports = mempty
222 , sourceRepos = []
223 , synopsis = mempty
224 , description = mempty
225 , category = mempty
226 , customFieldsPD = []
227 , setupBuildInfo = Nothing
228 , library = Nothing
229 , subLibraries = []
230 , foreignLibs = []
231 , executables = []
232 , testSuites = []
233 , benchmarks = []
234 , dataFiles = []
235 , dataDir = sameDirectory
236 , extraSrcFiles = []
237 , extraTmpFiles = []
238 , extraDocFiles = []
239 , extraFiles = []
242 -- ---------------------------------------------------------------------------
243 -- The Library type
245 -- | Does this package have a buildable PUBLIC library?
246 hasPublicLib :: PackageDescription -> Bool
247 hasPublicLib p =
248 case library p of
249 Just lib -> buildable (libBuildInfo lib)
250 Nothing -> False
252 -- | Does this package have any libraries?
253 hasLibs :: PackageDescription -> Bool
254 hasLibs p = any (buildable . libBuildInfo) (allLibraries p)
256 allLibraries :: PackageDescription -> [Library]
257 allLibraries p = maybeToList (library p) ++ subLibraries p
259 -- | If the package description has a buildable library section,
260 -- call the given function with the library build info as argument.
261 -- You probably want 'withLibLBI' if you have a 'LocalBuildInfo',
262 -- see the note in
263 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components"
264 -- for more information.
265 withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
266 withLib pkg_descr f =
267 sequence_ [f lib | lib <- allLibraries pkg_descr, buildable (libBuildInfo lib)]
269 -- ---------------------------------------------------------------------------
270 -- The Executable type
272 -- | does this package have any executables?
273 hasExes :: PackageDescription -> Bool
274 hasExes p = any (buildable . buildInfo) (executables p)
276 -- | Perform the action on each buildable 'Executable' in the package
277 -- description. You probably want 'withExeLBI' if you have a
278 -- 'LocalBuildInfo', see the note in
279 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components"
280 -- for more information.
281 withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
282 withExe pkg_descr f =
283 sequence_ [f exe | exe <- executables pkg_descr, buildable (buildInfo exe)]
285 -- ---------------------------------------------------------------------------
286 -- The TestSuite type
288 -- | Does this package have any test suites?
289 hasTests :: PackageDescription -> Bool
290 hasTests = any (buildable . testBuildInfo) . testSuites
292 -- | Perform an action on each buildable 'TestSuite' in a package.
293 -- You probably want 'withTestLBI' if you have a 'LocalBuildInfo', see the note in
294 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components"
295 -- for more information.
296 withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
297 withTest pkg_descr f =
298 sequence_ [f test | test <- testSuites pkg_descr, buildable (testBuildInfo test)]
300 -- ---------------------------------------------------------------------------
301 -- The Benchmark type
303 -- | Does this package have any benchmarks?
304 hasBenchmarks :: PackageDescription -> Bool
305 hasBenchmarks = any (buildable . benchmarkBuildInfo) . benchmarks
307 -- | Perform an action on each buildable 'Benchmark' in a package.
308 -- You probably want 'withBenchLBI' if you have a 'LocalBuildInfo', see the note in
309 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components"
310 -- for more information.
311 withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO ()
312 withBenchmark pkg_descr f =
313 sequence_ [f bench | bench <- benchmarks pkg_descr, buildable (benchmarkBuildInfo bench)]
315 -- ---------------------------------------------------------------------------
316 -- The ForeignLib type
318 -- | Does this package have any foreign libraries?
319 hasForeignLibs :: PackageDescription -> Bool
320 hasForeignLibs p = any (buildable . foreignLibBuildInfo) (foreignLibs p)
322 -- | Perform the action on each buildable 'ForeignLib' in the package
323 -- description.
324 withForeignLib :: PackageDescription -> (ForeignLib -> IO ()) -> IO ()
325 withForeignLib pkg_descr f =
326 sequence_
327 [ f flib
328 | flib <- foreignLibs pkg_descr
329 , buildable (foreignLibBuildInfo flib)
332 -- ---------------------------------------------------------------------------
333 -- The BuildInfo type
335 -- | All 'BuildInfo' in the 'PackageDescription':
336 -- libraries, executables, test-suites and benchmarks.
338 -- Useful for implementing package checks.
339 allBuildInfo :: PackageDescription -> [BuildInfo]
340 allBuildInfo pkg_descr =
341 [ bi | lib <- allLibraries pkg_descr, let bi = libBuildInfo lib
343 ++ [ bi | flib <- foreignLibs pkg_descr, let bi = foreignLibBuildInfo flib
345 ++ [ bi | exe <- executables pkg_descr, let bi = buildInfo exe
347 ++ [ bi | tst <- testSuites pkg_descr, let bi = testBuildInfo tst
349 ++ [ bi | tst <- benchmarks pkg_descr, let bi = benchmarkBuildInfo tst
352 -- | Return all of the 'BuildInfo's of enabled components, i.e., all of
353 -- the ones that would be built if you run @./Setup build@.
354 enabledBuildInfos :: PackageDescription -> ComponentRequestedSpec -> [BuildInfo]
355 enabledBuildInfos pkg enabled =
356 [ componentBuildInfo comp
357 | comp <- enabledComponents pkg enabled
360 -- ------------------------------------------------------------
362 -- * Utils
364 -- ------------------------------------------------------------
366 -- | Get the combined build-depends entries of all components.
367 allBuildDepends :: PackageDescription -> [Dependency]
368 allBuildDepends = targetBuildDepends <=< allBuildInfo
370 -- | Get the combined build-depends entries of all enabled components, per the
371 -- given request spec.
372 enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
373 enabledBuildDepends spec pd = targetBuildDepends =<< enabledBuildInfos spec pd
375 updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
376 updatePackageDescription (mb_lib_bi, exe_bi) p =
378 { executables = updateExecutables exe_bi (executables p)
379 , library = updateLibrary mb_lib_bi (library p)
381 where
382 updateLibrary :: Maybe BuildInfo -> Maybe Library -> Maybe Library
383 updateLibrary (Just bi) (Just lib) = Just (lib{libBuildInfo = bi `mappend` libBuildInfo lib})
384 updateLibrary Nothing mb_lib = mb_lib
385 updateLibrary (Just _) Nothing = Nothing
387 updateExecutables
388 :: [(UnqualComponentName, BuildInfo)]
389 -- \^[(exeName, new buildinfo)]
390 -> [Executable]
391 -- \^list of executables to update
392 -> [Executable]
393 -- \^list with exeNames updated
394 updateExecutables exe_bi' executables' = foldr updateExecutable executables' exe_bi'
396 updateExecutable
397 :: (UnqualComponentName, BuildInfo)
398 -- \^(exeName, new buildinfo)
399 -> [Executable]
400 -- \^list of executables to update
401 -> [Executable]
402 -- \^list with exeName updated
403 updateExecutable _ [] = []
404 updateExecutable exe_bi'@(name, bi) (exe : exes)
405 | exeName exe == name = exe{buildInfo = bi `mappend` buildInfo exe} : exes
406 | otherwise = exe : updateExecutable exe_bi' exes
408 -- -----------------------------------------------------------------------------
409 -- Source-representation of buildable components
411 -- | All the components in the package.
412 pkgComponents :: PackageDescription -> [Component]
413 pkgComponents pkg =
414 [CLib lib | lib <- allLibraries pkg]
415 ++ [CFLib flib | flib <- foreignLibs pkg]
416 ++ [CExe exe | exe <- executables pkg]
417 ++ [CTest tst | tst <- testSuites pkg]
418 ++ [CBench bm | bm <- benchmarks pkg]
420 -- | A list of all components in the package that are buildable,
421 -- i.e., were not marked with @buildable: False@. This does NOT
422 -- indicate if we are actually going to build the component,
423 -- see 'enabledComponents' instead.
425 -- @since 2.0.0.2
426 pkgBuildableComponents :: PackageDescription -> [Component]
427 pkgBuildableComponents = filter componentBuildable . pkgComponents
429 -- | A list of all components in the package that are enabled.
431 -- @since 2.0.0.2
432 enabledComponents :: PackageDescription -> ComponentRequestedSpec -> [Component]
433 enabledComponents pkg enabled = filter (componentEnabled enabled) $ pkgBuildableComponents pkg
435 lookupComponent :: PackageDescription -> ComponentName -> Maybe Component
436 lookupComponent pkg (CLibName name) =
437 fmap CLib $ find ((name ==) . libName) (allLibraries pkg)
438 lookupComponent pkg (CFLibName name) =
439 fmap CFLib $ find ((name ==) . foreignLibName) (foreignLibs pkg)
440 lookupComponent pkg (CExeName name) =
441 fmap CExe $ find ((name ==) . exeName) (executables pkg)
442 lookupComponent pkg (CTestName name) =
443 fmap CTest $ find ((name ==) . testName) (testSuites pkg)
444 lookupComponent pkg (CBenchName name) =
445 fmap CBench $ find ((name ==) . benchmarkName) (benchmarks pkg)
447 getComponent :: PackageDescription -> ComponentName -> Component
448 getComponent pkg cname =
449 case lookupComponent pkg cname of
450 Just cpnt -> cpnt
451 Nothing -> missingComponent
452 where
453 missingComponent =
454 error $
455 "internal error: the package description contains no "
456 ++ "component corresponding to "
457 ++ show cname
459 -- -----------------------------------------------------------------------------
460 -- Traversal Instances
462 instance L.HasBuildInfos PackageDescription where
463 traverseBuildInfos
465 ( PackageDescription
498 PackageDescription a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19
499 <$> (traverse . L.buildInfo) f x1 -- library
500 <*> (traverse . L.buildInfo) f x2 -- sub libraries
501 <*> (traverse . L.buildInfo) f x3 -- executables
502 <*> (traverse . L.buildInfo) f x4 -- foreign libs
503 <*> (traverse . L.buildInfo) f x5 -- test suites
504 <*> (traverse . L.buildInfo) f x6 -- benchmarks
505 <*> pure a20 -- data files
506 <*> pure a21 -- data dir
507 <*> pure a22 -- extra src files
508 <*> pure a23 -- extra temp files
509 <*> pure a24 -- extra doc files
510 <*> pure a25 -- extra files