Skip to content

Commit 484d159

Browse files
committed
Make a solving exe dep specify what exes are drawn from the package
Before there was simply a bool for lib vs exe, now the exe case as a `Maybe UnqualComponentName` for specific exe vs wildcard
1 parent 9969cd3 commit 484d159

File tree

4 files changed

+40
-25
lines changed

4 files changed

+40
-25
lines changed

cabal-install/Distribution/Solver/Modular/Builder.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -269,7 +269,7 @@ buildTree idx (IndependentGoals ind) igs =
269269
where
270270
-- Should a top-level goal allowed to be an executable style
271271
-- dependency? Well, I don't think it would make much difference
272-
topLevelGoal qpn = OpenGoal (Simple (Dep False {- not exe -} qpn (Constrained [])) ()) UserGoal
272+
topLevelGoal qpn = OpenGoal (Simple (Dep DRLib qpn (Constrained [])) ()) UserGoal
273273

274274
qpns | ind = makeIndependent igs
275275
| otherwise = L.map (Q (PackagePath DefaultNamespace QualToplevel)) igs

cabal-install/Distribution/Solver/Modular/Dependency.hs

Lines changed: 34 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ module Distribution.Solver.Modular.Dependency (
2121
, FlaggedDeps
2222
, FlaggedDep(..)
2323
, Dep(..)
24+
, DepRole(..)
2425
, showDep
2526
, flattenFlaggedDeps
2627
, QualifyOptions(..)
@@ -53,6 +54,7 @@ import qualified Data.List as L
5354
import Language.Haskell.Extension (Extension(..), Language(..))
5455

5556
import Distribution.Text
57+
import Distribution.Types.UnqualComponentName
5658

5759
import Distribution.Solver.Modular.ConflictSet (ConflictSet, ConflictMap)
5860
import Distribution.Solver.Modular.Flag
@@ -166,8 +168,23 @@ flattenFlaggedDeps = concatMap aux
166168
type TrueFlaggedDeps qpn = FlaggedDeps Component qpn
167169
type FalseFlaggedDeps qpn = FlaggedDeps Component qpn
168170

169-
-- | Is this dependency on an executable
170-
type IsExe = Bool
171+
172+
-- | Why do we depend on this package? The role of a dependency package is the
173+
-- components to be used from that package.
174+
--
175+
-- If 'Nothing', then we depend on all executables in the package. If 'Just
176+
-- name', then we depend on the executable with that name in the package.
177+
--
178+
-- TODO: add a similar field for 'Library' if allow depending on named
179+
-- libraries.
180+
data DepRole = DRLib
181+
| DRExe (Maybe UnqualComponentName)
182+
deriving (Eq, Show)
183+
184+
showDepRole :: DepRole -> String
185+
showDepRole DRLib = ""
186+
showDepRole (DRExe Nothing) = " (all exes) "
187+
showDepRole (DRExe (Just n)) = " (exe: " ++ display n ++ ") "
171188

172189
-- | A dependency (constraint) associates a package name with a
173190
-- constrained instance.
@@ -176,22 +193,20 @@ type IsExe = Bool
176193
-- is used both to record the dependencies as well as who's doing the
177194
-- depending; having a 'Functor' instance makes bugs where we don't distinguish
178195
-- these two far too likely. (By rights 'Dep' ought to have two type variables.)
179-
data Dep qpn = Dep IsExe qpn (CI qpn) -- ^ dependency on a package (possibly for executable
196+
data Dep qpn = Dep DepRole qpn (CI qpn) -- ^ dependency on a package (possibly for executable
180197
| Ext Extension -- ^ dependency on a language extension
181198
| Lang Language -- ^ dependency on a language version
182199
| Pkg PkgconfigName VR -- ^ dependency on a pkg-config package
183200
deriving (Eq, Show)
184201

185202
showDep :: Dep QPN -> String
186-
showDep (Dep is_exe qpn (Fixed i v) ) =
203+
showDep (Dep role qpn (Fixed i v) ) =
187204
(if P qpn /= v then showVar v ++ " => " else "") ++
188-
showQPN qpn ++
189-
(if is_exe then " (exe) " else "") ++ "==" ++ showI i
190-
showDep (Dep is_exe qpn (Constrained [(vr, v)])) =
191-
showVar v ++ " => " ++ showQPN qpn ++
192-
(if is_exe then " (exe) " else "") ++ showVR vr
193-
showDep (Dep is_exe qpn ci ) =
194-
showQPN qpn ++ (if is_exe then " (exe) " else "") ++ showCI ci
205+
showQPN qpn ++ showDepRole role ++ "==" ++ showI i
206+
showDep (Dep role qpn (Constrained [(vr, v)])) =
207+
showVar v ++ " => " ++ showQPN qpn ++ showDepRole role ++ showVR vr
208+
showDep (Dep role qpn ci ) =
209+
showQPN qpn ++ showDepRole role ++ showCI ci
195210
showDep (Ext ext) = "requires " ++ display ext
196211
showDep (Lang lang) = "requires " ++ display lang
197212
showDep (Pkg pn vr) = "requires pkg-config package "
@@ -243,11 +258,12 @@ qualifyDeps QO{..} (Q pp@(PackagePath ns q) pn) = go
243258
goD (Ext ext) _ = Ext ext
244259
goD (Lang lang) _ = Lang lang
245260
goD (Pkg pkn vr) _ = Pkg pkn vr
246-
goD (Dep is_exe dep ci) comp
247-
| is_exe = Dep is_exe (Q (PackagePath ns (QualExe pn dep)) dep) (fmap (Q pp) ci)
248-
| qBase dep = Dep is_exe (Q (PackagePath ns (QualBase pn)) dep) (fmap (Q pp) ci)
249-
| qSetup comp = Dep is_exe (Q (PackagePath ns (QualSetup pn)) dep) (fmap (Q pp) ci)
250-
| otherwise = Dep is_exe (Q (PackagePath ns inheritedQ) dep) (fmap (Q pp) ci)
261+
goD (Dep role dep ci) comp
262+
| DRExe _ <- role = goQ $ Q (PackagePath ns (QualExe pn dep)) dep
263+
| qBase dep = goQ $ Q (PackagePath ns (QualBase pn)) dep
264+
| qSetup comp = goQ $ Q (PackagePath ns (QualSetup pn)) dep
265+
| otherwise = goQ $ Q (PackagePath ns inheritedQ) dep
266+
where goQ qual = Dep role qual (fmap (Q pp) ci)
251267

252268
-- If P has a setup dependency on Q, and Q has a regular dependency on R, then
253269
-- we say that the 'Setup' qualifier is inherited: P has an (indirect) setup
@@ -290,7 +306,7 @@ unqualifyDeps = go
290306
go1 (Simple dep comp) = Simple (goD dep) comp
291307

292308
goD :: Dep QPN -> Dep PN
293-
goD (Dep is_exe qpn ci) = Dep is_exe (unq qpn) (fmap unq ci)
309+
goD (Dep role qpn ci) = Dep role (unq qpn) (fmap unq ci)
294310
goD (Ext ext) = Ext ext
295311
goD (Lang lang) = Lang lang
296312
goD (Pkg pn vr) = Pkg pn vr
@@ -362,7 +378,7 @@ instance ResetVar CI where
362378
resetVar v (Constrained vrs) = Constrained (L.map (\ (x, y) -> (x, resetVar v y)) vrs)
363379

364380
instance ResetVar Dep where
365-
resetVar v (Dep is_exe qpn ci) = Dep is_exe qpn (resetVar v ci)
381+
resetVar v (Dep role qpn ci) = Dep role qpn (resetVar v ci)
366382
resetVar _ (Ext ext) = Ext ext
367383
resetVar _ (Lang lang) = Lang lang
368384
resetVar _ (Pkg pn vr) = Pkg pn vr

cabal-install/Distribution/Solver/Modular/IndexConversion.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ convIPId pn' idx ipid =
9494
Nothing -> Nothing
9595
Just ipi -> let i = I (pkgVersion (sourcePackageId ipi)) (Inst ipid)
9696
pn = pkgName (sourcePackageId ipi)
97-
in Just (D.Simple (Dep False pn (Fixed i (P pn'))) ())
97+
in Just (D.Simple (Dep DRLib pn (Fixed i (P pn'))) ())
9898
-- NB: something we pick up from the
9999
-- InstalledPackageIndex is NEVER an executable
100100

@@ -297,12 +297,11 @@ convBranch pkg os arch cinfo pi@(PI pn _) fds comp getInfo ipns sexes (CondBranc
297297

298298
-- | Convert a Cabal dependency on a library to a solver-specific dependency.
299299
convLibDep :: PN -> Dependency -> Dep PN
300-
convLibDep pn' (Dependency pn vr) = Dep False {- not exe -} pn (Constrained [(vr, P pn')])
300+
convLibDep pn' (Dependency pn vr) = Dep DRLib pn (Constrained [(vr, P pn')])
301301

302302
-- | Convert a Cabal dependency on a executable (build-tools) to a solver-specific dependency.
303-
-- TODO do something about the name of the exe component itself
304303
convExeDep :: PN -> ExeDependency -> Dep PN
305-
convExeDep pn' (ExeDependency pn _ vr) = Dep True pn (Constrained [(vr, P pn')])
304+
convExeDep pn' (ExeDependency pn en vr) = Dep (DRExe en) pn (Constrained [(vr, P pn')])
306305

307306
-- | Convert setup dependencies
308307
convSetupBuildInfo :: PI PN -> SetupBuildInfo -> FlaggedDeps Component PN

cabal-install/Distribution/Solver/Modular/Validate.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -153,8 +153,8 @@ validate = cata go
153153
let qdeps = qualifyDeps qo qpn deps
154154
-- the new active constraints are given by the instance we have chosen,
155155
-- plus the dependency information we have for that instance
156-
-- TODO: is the False here right?
157-
let newactives = Dep False {- not exe -} qpn (Fixed i (P qpn)) : L.map (resetVar (P qpn)) (extractDeps pfa psa qdeps)
156+
-- TODO: is lib-only right here right?
157+
let newactives = Dep DRLib qpn (Fixed i (P qpn)) : L.map (resetVar (P qpn)) (extractDeps pfa psa qdeps)
158158
-- We now try to extend the partial assignment with the new active constraints.
159159
let mnppa = extend extSupported langSupported pkgPresent (P qpn) ppa newactives
160160
-- In case we continue, we save the scoped dependencies

0 commit comments

Comments
 (0)