Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Simple / BuildToolDepends.hs
blob486cd2049d9ef76f313e3049ab6613efacf1af59
1 -- |
2 --
3 -- This modules provides functions for working with both the legacy
4 -- "build-tools" field, and its replacement, "build-tool-depends". Prefer using
5 -- the functions contained to access those fields directly.
6 module Distribution.Simple.BuildToolDepends where
8 import Distribution.Compat.Prelude
9 import Prelude ()
11 import qualified Data.Map as Map
13 import Distribution.Package
14 import Distribution.PackageDescription
16 -- | Desugar a "build-tools" entry into proper a executable dependency if
17 -- possible.
19 -- An entry can be so desugared in two cases:
21 -- 1. The name in build-tools matches a locally defined executable. The
22 -- executable dependency produced is on that exe in the current package.
24 -- 2. The name in build-tools matches a hard-coded set of known tools. For now,
25 -- the executable dependency produced is one an executable in a package of
26 -- the same, but the hard-coding could just as well be per-key.
28 -- The first cases matches first.
29 desugarBuildTool
30 :: PackageDescription
31 -> LegacyExeDependency
32 -> Maybe ExeDependency
33 desugarBuildTool pkg led =
34 if foundLocal
35 then Just $ ExeDependency (packageName pkg) toolName reqVer
36 else Map.lookup name whiteMap
37 where
38 LegacyExeDependency name reqVer = led
39 toolName = mkUnqualComponentName name
40 foundLocal = toolName `elem` map exeName (executables pkg)
41 whitelist =
42 [ "hscolour"
43 , "haddock"
44 , "happy"
45 , "alex"
46 , "hsc2hs"
47 , "c2hs"
48 , "cpphs"
49 , "greencard"
50 , "hspec-discover"
52 whiteMap = Map.fromList $ flip map whitelist $ \n ->
53 (n, ExeDependency (mkPackageName n) (mkUnqualComponentName n) reqVer)
55 -- | Get everything from "build-tool-depends", along with entries from
56 -- "build-tools" that we know how to desugar.
58 -- This should almost always be used instead of just accessing the
59 -- `buildToolDepends` field directly.
60 getAllToolDependencies
61 :: PackageDescription
62 -> BuildInfo
63 -> [ExeDependency]
64 getAllToolDependencies pkg bi =
65 buildToolDepends bi ++ mapMaybe (desugarBuildTool pkg) (buildTools bi)
67 -- | Does the given executable dependency map to this current package?
69 -- This is a tiny function, but used in a number of places.
71 -- This function is only sound to call on `BuildInfo`s from the given package
72 -- description. This is because it just filters the package names of each
73 -- dependency, and does not check whether version bounds in fact exclude the
74 -- current package, or the referenced components in fact exist in the current
75 -- package.
77 -- This is OK because when a package is loaded, it is checked (in
78 -- `Distribution.Package.Check`) that dependencies matching internal components
79 -- do indeed have version bounds accepting the current package, and any
80 -- depended-on component in the current package actually exists. In fact this
81 -- check is performed by gathering the internal tool dependencies of each
82 -- component of the package according to this module, and ensuring those
83 -- properties on each so-gathered dependency.
85 -- version bounds and components of the package are unchecked. This is because
86 -- we sanitize exe deps so that the matching name implies these other
87 -- conditions.
88 isInternal :: PackageDescription -> ExeDependency -> Bool
89 isInternal pkg (ExeDependency n _ _) = n == packageName pkg
91 -- | Get internal "build-tool-depends", along with internal "build-tools"
93 -- This is a tiny function, but used in a number of places. The same
94 -- restrictions that apply to `isInternal` also apply to this function.
95 getAllInternalToolDependencies
96 :: PackageDescription
97 -> BuildInfo
98 -> [UnqualComponentName]
99 getAllInternalToolDependencies pkg bi =
100 [ toolname
101 | dep@(ExeDependency _ toolname _) <- getAllToolDependencies pkg bi
102 , isInternal pkg dep