@@ -53,13 +53,13 @@ import Distribution.Solver.Modular.Version
5353-- resolving these situations. However, the right thing to do is to
5454-- fix the problem there, so for now, shadowing is only activated if
5555-- explicitly requested.
56- convPIs :: OS -> Arch -> CompilerInfo -> Map PN [LabeledPackageConstraint ]
56+ convPIs :: Maybe OS -> Maybe Arch -> Maybe CompilerInfo -> Map PN [LabeledPackageConstraint ]
5757 -> ShadowPkgs -> StrongFlags -> SolveExecutables
5858 -> SI. InstalledPackageIndex -> CI. PackageIndex (SourcePackage loc )
5959 -> Index
60- convPIs os arch comp constraints sip strfl solveExes iidx sidx =
60+ convPIs mos march mcomp constraints sip strfl solveExes iidx sidx =
6161 mkIndex $
62- convIPI' sip iidx ++ convSPI' os arch comp constraints strfl solveExes sidx
62+ convIPI' sip iidx ++ convSPI' mos march mcomp constraints strfl solveExes sidx
6363
6464-- | Convert a Cabal installed package index to the simpler,
6565-- more uniform index format of the solver.
@@ -153,29 +153,29 @@ convIPId dr comp idx ipid =
153153
154154-- | Convert a cabal-install source package index to the simpler,
155155-- more uniform index format of the solver.
156- convSPI' :: OS -> Arch -> CompilerInfo -> Map PN [LabeledPackageConstraint ]
156+ convSPI' :: Maybe OS -> Maybe Arch -> Maybe CompilerInfo -> Map PN [LabeledPackageConstraint ]
157157 -> StrongFlags -> SolveExecutables
158158 -> CI. PackageIndex (SourcePackage loc ) -> [(PN , I , PInfo )]
159- convSPI' os arch cinfo constraints strfl solveExes =
160- L. map (convSP os arch cinfo constraints strfl solveExes) . CI. allPackages
159+ convSPI' mos march mcinfo constraints strfl solveExes =
160+ L. map (convSP mos march mcinfo constraints strfl solveExes) . CI. allPackages
161161
162162-- | Convert a single source package into the solver-specific format.
163- convSP :: OS -> Arch -> CompilerInfo -> Map PN [LabeledPackageConstraint ]
163+ convSP :: Maybe OS -> Maybe Arch -> Maybe CompilerInfo -> Map PN [LabeledPackageConstraint ]
164164 -> StrongFlags -> SolveExecutables -> SourcePackage loc -> (PN , I , PInfo )
165- convSP os arch cinfo constraints strfl solveExes (SourcePackage (PackageIdentifier pn pv) gpd _ _pl) =
165+ convSP mos march mcinfo constraints strfl solveExes (SourcePackage (PackageIdentifier pn pv) gpd _ _pl) =
166166 let i = I pv InRepo
167167 pkgConstraints = fromMaybe [] $ M. lookup pn constraints
168- in (pn, i, convGPD os arch cinfo pkgConstraints strfl solveExes pn gpd)
168+ in (pn, i, convGPD mos march mcinfo pkgConstraints strfl solveExes pn gpd)
169169
170170-- We do not use 'flattenPackageDescription' or 'finalizePD'
171171-- from 'Distribution.PackageDescription.Configuration' here, because we
172172-- want to keep the condition tree, but simplify much of the test.
173173
174174-- | Convert a generic package description to a solver-specific 'PInfo'.
175- convGPD :: OS -> Arch -> CompilerInfo -> [LabeledPackageConstraint ]
175+ convGPD :: Maybe OS -> Maybe Arch -> Maybe CompilerInfo -> [LabeledPackageConstraint ]
176176 -> StrongFlags -> SolveExecutables -> PN -> GenericPackageDescription
177177 -> PInfo
178- convGPD os arch cinfo constraints strfl solveExes pn
178+ convGPD mos march mcinfo constraints strfl solveExes pn
179179 (GenericPackageDescription pkg scannedVersion flags mlib sub_libs flibs exes tests benchs) =
180180 let
181181 fds = flagInfo strfl flags
@@ -184,7 +184,7 @@ convGPD os arch cinfo constraints strfl solveExes pn
184184 conv :: Monoid a => Component -> (a -> BuildInfo ) -> DependencyReason PN ->
185185 CondTree ConfVar [Dependency ] a -> FlaggedDeps PN
186186 conv comp getInfo dr =
187- convCondTree M. empty dr pkg os arch cinfo pn fds comp getInfo solveExes .
187+ convCondTree M. empty dr pkg mos march mcinfo pn fds comp getInfo solveExes .
188188 addBuildableCondition getInfo
189189
190190 initDR = DependencyReason pn M. empty S. empty
@@ -233,7 +233,7 @@ convGPD os arch cinfo constraints strfl solveExes pn
233233 , compIsBuildable = IsBuildable $ testCondition (buildable . libBuildInfo) lib /= Just False
234234 }
235235
236- testCondition = testConditionForComponent os arch cinfo constraints
236+ testCondition = testConditionForComponent mos march mcinfo constraints
237237
238238 isPrivate LibraryVisibilityPrivate = True
239239 isPrivate LibraryVisibilityPublic = False
@@ -246,14 +246,14 @@ convGPD os arch cinfo constraints strfl solveExes pn
246246-- before dependency solving. Additionally, this function only considers flags
247247-- that are set by unqualified flag constraints, and it doesn't check the
248248-- intra-package dependencies of a component.
249- testConditionForComponent :: OS
250- -> Arch
251- -> CompilerInfo
249+ testConditionForComponent :: Maybe OS
250+ -> Maybe Arch
251+ -> Maybe CompilerInfo
252252 -> [LabeledPackageConstraint ]
253253 -> (a -> Bool )
254254 -> CondTree ConfVar [Dependency ] a
255255 -> Maybe Bool
256- testConditionForComponent os arch cinfo constraints p tree =
256+ testConditionForComponent mos march mcinfo constraints p tree =
257257 case go $ extractCondition p tree of
258258 Lit True -> Just True
259259 Lit False -> Just False
@@ -269,16 +269,17 @@ testConditionForComponent os arch cinfo constraints p tree =
269269 -- function was copied from convBranch and
270270 -- Distribution.Types.Condition.simplifyCondition.
271271 go :: Condition ConfVar -> Condition ConfVar
272- go (Var (OS os')) = Lit (os == os')
273- go (Var (Arch arch')) = Lit (arch == arch')
274- go (Var (Impl cf cvr))
275- | matchImpl (compilerInfoId cinfo) ||
276- -- fixme: Nothing should be treated as unknown, rather than empty
277- -- list. This code should eventually be changed to either
278- -- support partial resolution of compiler flags or to
279- -- complain about incompletely configured compilers.
280- any matchImpl (fromMaybe [] $ compilerInfoCompat cinfo) = Lit True
281- | otherwise = Lit False
272+ go (Var (OS os')) | Just os <- mos = Lit (os == os')
273+ go (Var (Arch arch')) | Just arch <- march = Lit (arch == arch')
274+ go (Var (Impl cf cvr)) | Just cinfo <- mcinfo =
275+ if matchImpl (compilerInfoId cinfo) ||
276+ -- fixme: Nothing should be treated as unknown, rather than empty
277+ -- list. This code should eventually be changed to either
278+ -- support partial resolution of compiler flags or to
279+ -- complain about incompletely configured compilers.
280+ any matchImpl (fromMaybe [] $ compilerInfoCompat cinfo)
281+ then Lit True
282+ else Lit False
282283 where
283284 matchImpl (CompilerId cf' cv) = cf == cf' && checkVR cvr cv
284285 go (Var (PackageFlag f))
@@ -325,12 +326,13 @@ flagInfo (StrongFlags strfl) =
325326-- | Convert condition trees to flagged dependencies. Mutually
326327-- recursive with 'convBranch'. See 'convBranch' for an explanation
327328-- of all arguments preceding the input 'CondTree'.
328- convCondTree :: Map FlagName Bool -> DependencyReason PN -> PackageDescription -> OS -> Arch -> CompilerInfo -> PN -> FlagInfo ->
329+ convCondTree :: Map FlagName Bool -> DependencyReason PN -> PackageDescription ->
330+ Maybe OS -> Maybe Arch -> Maybe CompilerInfo -> PN -> FlagInfo ->
329331 Component ->
330332 (a -> BuildInfo ) ->
331333 SolveExecutables ->
332334 CondTree ConfVar [Dependency ] a -> FlaggedDeps PN
333- convCondTree flags dr pkg os arch cinfo pn fds comp getInfo solveExes@ (SolveExecutables solveExes') (CondNode info ds branches) =
335+ convCondTree flags dr pkg mos march mcinfo pn fds comp getInfo solveExes@ (SolveExecutables solveExes') (CondNode info ds branches) =
334336 -- Merge all library and build-tool dependencies at every level in
335337 -- the tree of flagged dependencies. Otherwise 'extractCommon'
336338 -- could create duplicate dependencies, and the number of
@@ -344,7 +346,7 @@ convCondTree flags dr pkg os arch cinfo pn fds comp getInfo solveExes@(SolveExec
344346 ++ L. map (\ e -> D. Simple (LDep dr (Ext e)) comp) (allExtensions bi) -- unconditional extension dependencies
345347 ++ L. map (\ l -> D. Simple (LDep dr (Lang l)) comp) (allLanguages bi) -- unconditional language dependencies
346348 ++ L. map (\ (PkgconfigDependency pkn vr) -> D. Simple (LDep dr (Pkg pkn vr)) comp) (pkgconfigDepends bi) -- unconditional pkg-config dependencies
347- ++ concatMap (convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes) branches
349+ ++ concatMap (convBranch flags dr pkg mos march mcinfo pn fds comp getInfo solveExes) branches
348350 -- build-tools dependencies
349351 -- NB: Only include these dependencies if SolveExecutables
350352 -- is True. It might be false in the legacy solver
@@ -453,20 +455,20 @@ mergeSimpleDeps deps = L.map (uncurry toFlaggedDep) (M.toList merged) ++ unmerge
453455convBranch :: Map FlagName Bool
454456 -> DependencyReason PN
455457 -> PackageDescription
456- -> OS
457- -> Arch
458- -> CompilerInfo
458+ -> Maybe OS
459+ -> Maybe Arch
460+ -> Maybe CompilerInfo
459461 -> PN
460462 -> FlagInfo
461463 -> Component
462464 -> (a -> BuildInfo )
463465 -> SolveExecutables
464466 -> CondBranch ConfVar [Dependency ] a
465467 -> FlaggedDeps PN
466- convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes (CondBranch c' t' mf') =
468+ convBranch flags dr pkg mos march mcinfo pn fds comp getInfo solveExes (CondBranch c' t' mf') =
467469 go c'
468- (\ flags' dr' -> convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo solveExes t')
469- (\ flags' dr' -> maybe [] (convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo solveExes) mf')
470+ (\ flags' dr' -> convCondTree flags' dr' pkg mos march mcinfo pn fds comp getInfo solveExes t')
471+ (\ flags' dr' -> maybe [] (convCondTree flags' dr' pkg mos march mcinfo pn fds comp getInfo solveExes) mf')
470472 flags dr
471473 where
472474 go :: Condition ConfVar
@@ -496,19 +498,19 @@ convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes (CondBranch
496498 ++ [ Flagged (FN pn fn) (fds M. ! fn) (t (addFlag True ) (addFlagValue FlagTrue ))
497499 (f (addFlag False ) (addFlagValue FlagFalse )) ]
498500 go (Var (OS os')) t f
499- | os == os' = t
500- | otherwise = f
501+ | Just os <- mos = if os == os' then t else f
501502 go (Var (Arch arch')) t f
502- | arch == arch' = t
503- | otherwise = f
503+ | Just arch <- march = if arch == arch' then t else f
504504 go (Var (Impl cf cvr)) t f
505- | matchImpl (compilerInfoId cinfo) ||
505+ | Just cinfo <- mcinfo =
506+ if matchImpl (compilerInfoId cinfo) ||
506507 -- fixme: Nothing should be treated as unknown, rather than empty
507508 -- list. This code should eventually be changed to either
508509 -- support partial resolution of compiler flags or to
509510 -- complain about incompletely configured compilers.
510- any matchImpl (fromMaybe [] $ compilerInfoCompat cinfo) = t
511- | otherwise = f
511+ any matchImpl (fromMaybe [] $ compilerInfoCompat cinfo)
512+ then t
513+ else f
512514 where
513515 matchImpl (CompilerId cf' cv) = cf == cf' && checkVR cvr cv
514516
0 commit comments