Add “Ignore warning” option to cabal check
[cabal.git] / cabal-install / src / Distribution / Client / ProjectPlanning / SetupPolicy.hs
blob86bc044342e2ec6fa98cf84a9e9fd3970e3574c2
1 {-# LANGUAGE TypeFamilies #-}
3 -- | Setup.hs script policy
4 --
5 -- Handling for Setup.hs scripts is a bit tricky, part of it lives in the
6 -- solver phase, and part in the elaboration phase. We keep the helper
7 -- functions for both phases together here so at least you can see all of it
8 -- in one place.
9 --
10 -- There are four major cases for Setup.hs handling:
12 -- 1. @build-type@ Custom with a @custom-setup@ section
13 -- 2. @build-type@ Custom without a @custom-setup@ section
14 -- 3. @build-type@ not Custom with @cabal-version > $our-cabal-version@
15 -- 4. @build-type@ not Custom with @cabal-version <= $our-cabal-version@
17 -- It's also worth noting that packages specifying @cabal-version: >= 1.23@
18 -- or later that have @build-type@ Custom will always have a @custom-setup@
19 -- section. Therefore in case 2, the specified @cabal-version@ will always be
20 -- less than 1.23.
22 -- In cases 1 and 2 we obviously have to build an external Setup.hs script,
23 -- while in case 4 we can use the internal library API.
25 -- @since 3.12.0.0
26 module Distribution.Client.ProjectPlanning.SetupPolicy
27 ( mkDefaultSetupDeps
28 , packageSetupScriptStyle
29 , packageSetupScriptSpecVersion
30 , NonSetupLibDepSolverPlanPackage (..)
32 where
34 import Distribution.Client.Compat.Prelude
35 import Prelude ()
37 import Distribution.Client.ProjectPlanning.Types (SetupScriptStyle (..))
38 import Distribution.Client.SolverInstallPlan (SolverPlanPackage)
39 import Distribution.Solver.Types.ComponentDeps (ComponentDeps)
40 import qualified Distribution.Solver.Types.ComponentDeps as CD
41 import Distribution.Solver.Types.ResolverPackage (resolverPackageLibDeps)
42 import Distribution.Solver.Types.SolverId (SolverId)
44 import Distribution.CabalSpecVersion
46 import Distribution.Package
47 import Distribution.PackageDescription
48 import Distribution.Simple.Compiler
49 import Distribution.System
51 import Distribution.Simple.Utils
52 import Distribution.Version
54 import Distribution.Compat.Graph (IsNode (..))
55 import qualified Distribution.Compat.Graph as Graph
57 -- | Work out the 'SetupScriptStyle' given the package description.
59 -- @since 3.12.0.0
60 packageSetupScriptStyle :: PackageDescription -> SetupScriptStyle
61 packageSetupScriptStyle pkg
62 | buildType pkg == Custom
63 , Just setupbi <- setupBuildInfo pkg -- does have a custom-setup stanza
64 , not (defaultSetupDepends setupbi) -- but not one we added ourselves
66 SetupCustomExplicitDeps
67 | buildType pkg == Custom
68 , Just setupbi <- setupBuildInfo pkg -- does have a custom-setup stanza
69 , defaultSetupDepends setupbi -- that we had to add ourselves
71 SetupCustomImplicitDeps
72 | buildType pkg == Custom
73 , Nothing <- setupBuildInfo pkg -- we get this case pre-solver
75 SetupCustomImplicitDeps
76 -- The specified @cabal-version@ is newer that the last we know about.
77 -- Here we could fail but we are optimist and build an external setup script.
78 | specVersion pkg > cabalSpecLatest =
79 SetupNonCustomExternalLib
80 | otherwise =
81 SetupNonCustomInternalLib
83 -- | Part of our Setup.hs handling policy is implemented by getting the solver
84 -- to work out setup dependencies for packages. The solver already handles
85 -- packages that explicitly specify setup dependencies, but we can also tell
86 -- the solver to treat other packages as if they had setup dependencies.
87 -- That's what this function does, it gets called by 'planPackages' for all
88 -- packages that don't already have setup dependencies.
90 -- The dependencies we want to add is different for each 'SetupScriptStyle'.
92 -- Note in addition to adding setup dependencies, we also use
93 -- 'addSetupCabalMinVersionConstraint' (in 'planPackages') to require
94 -- @Cabal >= 1.20@ for Setup scripts.
96 -- @since 3.12.0.0
97 mkDefaultSetupDeps
98 :: Compiler
99 -> Platform
100 -> PackageDescription
101 -> Maybe [Dependency]
102 mkDefaultSetupDeps compiler platform pkg =
103 case packageSetupScriptStyle pkg of
104 -- For packages with build type custom that do not specify explicit
105 -- setup dependencies, we add a dependency on Cabal and a number
106 -- of other packages.
107 SetupCustomImplicitDeps ->
108 Just $
109 [ Dependency depPkgname anyVersion mainLibSet
110 | depPkgname <- legacyCustomSetupPkgs compiler platform
112 ++ [ Dependency cabalPkgname cabalConstraint mainLibSet
113 | packageName pkg /= cabalPkgname
115 where
116 -- The Cabal dep is slightly special:
117 -- \* We omit the dep for the Cabal lib itself, since it bootstraps.
118 -- \* We constrain it to be < 1.25
120 -- Note: we also add a global constraint to require Cabal >= 1.20
121 -- for Setup scripts (see use addSetupCabalMinVersionConstraint).
123 cabalConstraint =
124 orLaterVersion (csvToVersion (specVersion pkg))
125 `intersectVersionRanges` earlierVersion cabalCompatMaxVer
126 -- The idea here is that at some point we will make significant
127 -- breaking changes to the Cabal API that Setup.hs scripts use.
128 -- So for old custom Setup scripts that do not specify explicit
129 -- constraints, we constrain them to use a compatible Cabal version.
130 cabalCompatMaxVer = mkVersion [1, 25]
132 -- For other build types (like Simple) if we still need to compile an
133 -- external Setup.hs, it'll be one of the simple ones that only depends
134 -- on Cabal and base.
135 SetupNonCustomExternalLib ->
136 Just
137 [ Dependency cabalPkgname cabalConstraint mainLibSet
138 , Dependency basePkgname anyVersion mainLibSet
140 where
141 cabalConstraint = orLaterVersion (csvToVersion (specVersion pkg))
143 -- The internal setup wrapper method has no deps at all.
144 SetupNonCustomInternalLib -> Just []
145 -- This case gets ruled out by the caller, planPackages, see the note
146 -- above in the SetupCustomImplicitDeps case.
147 SetupCustomExplicitDeps ->
148 error $
149 "mkDefaultSetupDeps: called for a package with explicit "
150 ++ "setup deps: "
151 ++ prettyShow (packageId pkg)
152 where
153 -- we require one less
155 -- This maps e.g. CabalSpecV3_0 to mkVersion [2,5]
156 csvToVersion :: CabalSpecVersion -> Version
157 csvToVersion = mkVersion . cabalSpecMinimumLibraryVersion
159 -- | A newtype for 'SolverPlanPackage' for which the
160 -- dependency graph considers only dependencies on libraries which are
161 -- NOT from setup dependencies. Used to compute the set
162 -- of packages needed for profiling and dynamic libraries.
164 -- @since 3.12.0.0
165 newtype NonSetupLibDepSolverPlanPackage = NonSetupLibDepSolverPlanPackage
166 {unNonSetupLibDepSolverPlanPackage :: SolverPlanPackage}
168 instance Package NonSetupLibDepSolverPlanPackage where
169 packageId (NonSetupLibDepSolverPlanPackage spkg) =
170 packageId spkg
172 instance IsNode NonSetupLibDepSolverPlanPackage where
173 type Key NonSetupLibDepSolverPlanPackage = SolverId
175 nodeKey (NonSetupLibDepSolverPlanPackage spkg) =
176 nodeKey spkg
178 nodeNeighbors (NonSetupLibDepSolverPlanPackage spkg) =
179 ordNub $ CD.nonSetupDeps (resolverPackageLibDeps spkg)
181 -- | Work out which version of the Cabal we will be using to talk to the
182 -- Setup.hs interface for this package.
184 -- This depends somewhat on the 'SetupScriptStyle' but most cases are a result
185 -- of what the solver picked for us, based on the explicit setup deps or the
186 -- ones added implicitly by 'mkDefaultSetupDeps'.
188 -- @since 3.12.0.0
189 packageSetupScriptSpecVersion
190 :: SetupScriptStyle
191 -> PackageDescription
192 -> Graph.Graph NonSetupLibDepSolverPlanPackage
193 -> ComponentDeps [SolverId]
194 -> Version
195 -- We're going to be using the internal Cabal library, so the spec version of
196 -- that is simply the version of the Cabal library that cabal-install has been
197 -- built with.
198 packageSetupScriptSpecVersion SetupNonCustomInternalLib _ _ _ =
199 cabalVersion
200 -- If we happen to be building the Cabal lib itself then because that
201 -- bootstraps itself then we use the version of the lib we're building.
202 packageSetupScriptSpecVersion SetupCustomImplicitDeps pkg _ _
203 | packageName pkg == cabalPkgname =
204 packageVersion pkg
205 -- In all other cases we have a look at what version of the Cabal lib the
206 -- solver picked. Or if it didn't depend on Cabal at all (which is very rare)
207 -- then we look at the .cabal file to see what spec version it declares.
208 packageSetupScriptSpecVersion _ pkg libDepGraph deps =
209 case find ((cabalPkgname ==) . packageName) setupLibDeps of
210 Just dep -> packageVersion dep
211 Nothing -> mkVersion (cabalSpecMinimumLibraryVersion (specVersion pkg))
212 where
213 setupLibDeps =
214 map packageId $
215 fromMaybe [] $
216 Graph.closure libDepGraph (CD.setupDeps deps)
218 cabalPkgname, basePkgname :: PackageName
219 cabalPkgname = mkPackageName "Cabal"
220 basePkgname = mkPackageName "base"
222 legacyCustomSetupPkgs :: Compiler -> Platform -> [PackageName]
223 legacyCustomSetupPkgs compiler (Platform _ os) =
224 map mkPackageName $
225 [ "array"
226 , "base"
227 , "binary"
228 , "bytestring"
229 , "containers"
230 , "deepseq"
231 , "directory"
232 , "filepath"
233 , "pretty"
234 , "process"
235 , "time"
236 , "transformers"
238 ++ ["Win32" | os == Windows]
239 ++ ["unix" | os /= Windows]
240 ++ ["ghc-prim" | isGHC]
241 ++ ["template-haskell" | isGHC]
242 ++ ["old-time" | notGHC710]
243 where
244 isGHC = compilerCompatFlavor GHC compiler
245 notGHC710 = case compilerCompatVersion GHC compiler of
246 Nothing -> False
247 Just v -> v <= mkVersion [7, 9]