Skip to content

Commit

Permalink
finalizePackageDescription BC.
Browse files Browse the repository at this point in the history
Signed-off-by: Edward Z. Yang <[email protected]>
  • Loading branch information
ezyang committed Jul 21, 2016
1 parent c1615bb commit 193f49d
Show file tree
Hide file tree
Showing 14 changed files with 52 additions and 35 deletions.
2 changes: 1 addition & 1 deletion Cabal/Distribution/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ data PackageDescription
-- PackageDescription we are, the contents of this field are
-- either nonsense, or the collected dependencies of *all* the
-- components in this package. buildDepends is initialized by
-- 'finalizePackageDescription' and 'flattenPackageDescription';
-- 'finalizePD' and 'flattenPackageDescription';
-- prior to that, dependency info is stored in the 'CondTree'
-- built around a 'GenericPackageDescription'. When this
-- resolution is done, dependency info is written to the inner
Expand Down
4 changes: 2 additions & 2 deletions Cabal/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1283,7 +1283,7 @@ checkPackageVersions pkg =
-- pick a single "typical" configuration and check if that has an
-- open upper bound. To get a typical configuration we finalise
-- using no package index and the current platform.
finalised = finalizePackageDescription
finalised = finalizePD
[] defaultComponentEnabled (const True) buildPlatform
(unknownCompilerInfo
(CompilerId buildCompilerFlavor (Version [] [])) NoAbiTag)
Expand All @@ -1295,7 +1295,7 @@ checkPackageVersions pkg =
baseDeps =
[ vr | Dependency (PackageName "base") vr <- buildDepends pkg' ]

-- Just in case finalizePackageDescription fails for any reason,
-- Just in case finalizePD fails for any reason,
-- or if the package doesn't depend on the base package at all,
-- then we will just skip the check, since boundedAbove noVersion = True
_ -> noVersion
Expand Down
21 changes: 18 additions & 3 deletions Cabal/Distribution/PackageDescription/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,13 @@
-- Portability : portable
--
-- This is about the cabal configurations feature. It exports
-- 'finalizePackageDescription' and 'flattenPackageDescription' which are
-- 'finalizePD' and 'flattenPackageDescription' which are
-- functions for converting 'GenericPackageDescription's down to
-- 'PackageDescription's. It has code for working with the tree of conditions
-- and resolving or flattening conditions.

module Distribution.PackageDescription.Configuration (
finalizePD,
finalizePackageDescription,
flattenPackageDescription,

Expand Down Expand Up @@ -553,7 +554,7 @@ instance Semigroup PDTagged where
-- On success, it will return the package description and the full flag
-- assignment chosen.
--
finalizePackageDescription ::
finalizePD ::
FlagAssignment -- ^ Explicitly specified flag assignments
-> ComponentEnabledSpec
-> (Dependency -> Bool) -- ^ Is a given dependency satisfiable from the set of
Expand All @@ -567,7 +568,7 @@ finalizePackageDescription ::
(PackageDescription, FlagAssignment)
-- ^ Either missing dependencies or the resolved package
-- description along with the flag assignments chosen.
finalizePackageDescription userflags enabled satisfyDep
finalizePD userflags enabled satisfyDep
(Platform arch os) impl constraints
(GenericPackageDescription pkg flags libs0 exes0 tests0 bms0) =
case resolveFlags of
Expand Down Expand Up @@ -611,6 +612,20 @@ finalizePackageDescription userflags enabled satisfyDep
then DepOk
else MissingDeps missingDeps

{-# DEPRECATED finalizePackageDescription "This function now always assumes tests and benchmarks are disabled; use finalizePD with ComponentEnabledSpec to specify something more specific." #-}
finalizePackageDescription ::
FlagAssignment -- ^ Explicitly specified flag assignments
-> (Dependency -> Bool) -- ^ Is a given dependency satisfiable from the set of
-- available packages? If this is unknown then use
-- True.
-> Platform -- ^ The 'Arch' and 'OS'
-> CompilerInfo -- ^ Compiler information
-> [Dependency] -- ^ Additional constraints
-> GenericPackageDescription
-> Either [Dependency]
(PackageDescription, FlagAssignment)
finalizePackageDescription flags = finalizePD flags defaultComponentEnabled

{-
let tst_p = (CondNode [1::Int] [Distribution.Package.Dependency "a" AnyVersion] [])
let tst_p2 = (CondNode [1::Int] [Distribution.Package.Dependency "a" (EarlierVersion (Version [1,0] [])), Distribution.Package.Dependency "a" (LaterVersion (Version [2,0] []))] [])
Expand Down
10 changes: 5 additions & 5 deletions Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -807,7 +807,7 @@ checkExactConfiguration pkg_descr0 cfg = do
--
-- It must be *any libraries that might be* defined rather than the
-- actual definitions, because these depend on conditionals in the .cabal
-- file, and we haven't resolved them yet. finalizePackageDescription
-- file, and we haven't resolved them yet. finalizePD
-- does the resolution of conditionals, and it takes internalPackageSet
-- as part of its input.
getInternalPackages :: GenericPackageDescription
Expand All @@ -832,7 +832,7 @@ getInternalPackages pkg_descr0 =


-- | Returns true if a dependency is satisfiable. This is to be passed
-- to finalizePackageDescription.
-- to finalizePD.
dependencySatisfiable
:: Bool
-> InstalledPackageIndex -- ^ installed set
Expand All @@ -848,7 +848,7 @@ dependencySatisfiable
-- line. Thus we only consult the 'requiredDepsMap'. Note that
-- we're not doing the version range check, so if there's some
-- dependency that wasn't specified on the command line,
-- 'finalizePackageDescription' will fail.
-- 'finalizePD' will fail.
--
-- TODO: mention '--exact-configuration' in the error message
-- when this fails?
Expand Down Expand Up @@ -891,7 +891,7 @@ relaxPackageDeps (RelaxDepsSome allowNewerDeps') gpd =
else d

-- | Finalize a generic package description. The workhorse is
-- 'finalizePackageDescription' but there's a bit of other nattering
-- 'finalizePD' but there's a bit of other nattering
-- about necessary.
--
-- TODO: what exactly is the business with @flaggedTests@ and
Expand All @@ -911,7 +911,7 @@ configureFinalizedPackage verbosity cfg enabled
allConstraints satisfies comp compPlatform pkg_descr0 = do

(pkg_descr0', flags) <-
case finalizePackageDescription
case finalizePD
(configConfigurationsFlags cfg)
enabled
satisfies
Expand Down
8 changes: 5 additions & 3 deletions Cabal/changelog
Original file line number Diff line number Diff line change
Expand Up @@ -33,11 +33,13 @@
such components, regardless of whether or not they have
been enabled; if you only want enabled components,
use 'withTestLBI' and 'withBenchLBI'.
'componentEnabled', 'enabledComponents' and
'finalizePackageDescription' now takes an extra argument
'finalizePackageDescription' is deprecated:
its replacement 'finalizePD' now takes an extra argument
'ComponentEnabledSpec' which specifies what components
are to be enabled: use this instead of modifying the
'Component' in a 'GenericPackageDescription'.
'Component' in a 'GenericPackageDescription'. (As
it's not possible now, 'finalizePackageDescription'
will assume tests/benchmarks are disabled.)
If you only need to test if a component is buildable
(i.e., it is marked buildable in the Cabal file)
use the new function 'componentBuildable'.
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ import qualified Distribution.PackageDescription as PkgDesc
import Distribution.PackageDescription.Parse
( readPackageDescription )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
( finalizePD )
import Distribution.Version
( anyVersion, thisVersion )
import Distribution.Simple.Utils as Utils
Expand Down Expand Up @@ -386,8 +386,8 @@ configurePackage verbosity platform comp scriptOptions configFlags
configTests = toFlag (TestStanzas `elem` stanzas)
}

pkg = case finalizePackageDescription flags (enableStanzas stanzas)
pkg = case finalizePD flags (enableStanzas stanzas)
(const True)
platform comp [] gpkg of
Left _ -> error "finalizePackageDescription ReadyPackage failed"
Left _ -> error "finalizePD ReadyPackage failed"
Right (desc, _) -> desc
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/Dependency.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ import Distribution.Package
import qualified Distribution.PackageDescription as PD
import qualified Distribution.PackageDescription.Configuration as PD
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
( finalizePD )
import Distribution.Client.PackageUtils
( externalBuildDepends )
import Distribution.Version
Expand Down Expand Up @@ -847,8 +847,8 @@ configuredPackageProblems platform cinfo
-- of the `nubOn` in `mergeDeps`.
requiredDeps :: [Dependency]
requiredDeps =
--TODO: use something lower level than finalizePackageDescription
case finalizePackageDescription specifiedFlags
--TODO: use something lower level than finalizePD
case finalizePD specifiedFlags
(enableStanzas stanzas)
(const True)
platform cinfo
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/Dependency/TopDown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Distribution.PackageDescription
import Distribution.Client.PackageUtils
( externalBuildDepends )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription, flattenPackageDescription )
( finalizePD, flattenPackageDescription )
import Distribution.Version
( Version(..), VersionRange, withinRange, simplifyVersionRange
, UpperBound(..), asVersionIntervals )
Expand Down Expand Up @@ -396,7 +396,7 @@ pruneBottomUp platform comp constraints =
| dep <- missing ]

configure cs (UnconfiguredPackage (SourcePackage _ pkg _ _) _ flags stanzas) =
finalizePackageDescription flags (enableStanzas stanzas) (dependencySatisfiable cs)
finalizePD flags (enableStanzas stanzas) (dependencySatisfiable cs)
platform comp [] pkg
dependencySatisfiable cs =
not . null . PackageIndex.lookupDependency (Constraints.choices cs)
Expand Down Expand Up @@ -425,7 +425,7 @@ configurePackage platform cinfo available spkg = case spkg of
(configure apkg)
where
configure (UnconfiguredPackage apkg@(SourcePackage _ p _ _) _ flags stanzas) =
case finalizePackageDescription flags (enableStanzas stanzas) dependencySatisfiable
case finalizePD flags (enableStanzas stanzas) dependencySatisfiable
platform cinfo [] p of
Left missing -> Left missing
Right (pkg, flags') -> Right $
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/GenBounds.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import Distribution.Package
import Distribution.PackageDescription
( buildDepends )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
( finalizePD )
import Distribution.PackageDescription.Parse
( readPackageDescription )
import Distribution.Simple.LocalBuildInfo
Expand Down Expand Up @@ -111,10 +111,10 @@ genBounds verbosity packageDBs repoCtxt comp platform conf mSandboxPkgInfo
gpd <- readPackageDescription verbosity path
-- NB: We don't enable tests or benchmarks, since often they
-- don't really have useful bounds.
let epd = finalizePackageDescription [] defaultComponentEnabled
let epd = finalizePD [] defaultComponentEnabled
(const True) platform cinfo [] gpd
case epd of
Left _ -> putStrLn "finalizePackageDescription failed"
Left _ -> putStrLn "finalizePD failed"
Right (pd,_) -> do
let needBounds = filter (not . hasUpperBound . depVersion) $
buildDepends pd
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,7 @@ import Distribution.PackageDescription
( PackageDescription, GenericPackageDescription(..), Flag(..)
, FlagName(..), FlagAssignment )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
( finalizePD )
import Distribution.ParseUtils
( showPWarning )
import Distribution.Version
Expand Down Expand Up @@ -1302,10 +1302,10 @@ installReadyPackage platform cinfo configFlags
configTests = toFlag (TestStanzas `elem` stanzas)
} source pkg pkgoverride
where
pkg = case finalizePackageDescription flags (enableStanzas stanzas)
pkg = case finalizePD flags (enableStanzas stanzas)
(const True)
platform cinfo [] gpkg of
Left _ -> error "finalizePackageDescription ReadyPackage failed"
Left _ -> error "finalizePD ReadyPackage failed"
Right (desc, _) -> desc

fetchSourcePackage
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/InstallSymlink.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ import qualified Distribution.PackageDescription as PackageDescription
import Distribution.PackageDescription
( PackageDescription )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
( finalizePD )
import Distribution.Simple.Setup
( ConfigFlags(..), fromFlag, fromFlagOrDefault, flagToMaybe )
import qualified Distribution.Simple.InstallDirs as InstallDirs
Expand Down Expand Up @@ -145,10 +145,10 @@ symlinkBinaries platform comp configFlags installFlags plan =
pkgDescription (ReadyPackage (ConfiguredPackage
_ (SourcePackage _ pkg _ _)
flags stanzas _)) =
case finalizePackageDescription flags (enableStanzas stanzas)
case finalizePD flags (enableStanzas stanzas)
(const True)
platform cinfo [] pkg of
Left _ -> error "finalizePackageDescription ReadyPackage failed"
Left _ -> error "finalizePD ReadyPackage failed"
Right (desc, _) -> desc

-- This is sadly rather complicated. We're kind of re-doing part of the
Expand Down
2 changes: 1 addition & 1 deletion cabal-install/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1065,7 +1065,7 @@ elaborateInstallPlan platform compiler compilerprogdb
--
pkgSourceId = pkgid
pkgDescription = let Right (desc, _) =
PD.finalizePackageDescription
PD.finalizePD
flags enabled (const True)
platform (compilerInfo compiler)
[] gdesc
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ convSP os arch cinfo strfl (SourcePackage (PackageIdentifier pn pv) gpd _ _pl) =
let i = I pv InRepo
in (pn, i, convGPD os arch cinfo strfl (PI pn i) gpd)

-- We do not use 'flattenPackageDescription' or 'finalizePackageDescription'
-- We do not use 'flattenPackageDescription' or 'finalizePD'
-- from 'Distribution.PackageDescription.Configuration' here, because we
-- want to keep the condition tree, but simplify much of the test.

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ import Distribution.Solver.Types.Variable
`GenericPackageDescription` can be turned into a `PackageDescription` in
two ways:
a. `finalizePackageDescription` does the proper translation, by taking
a. `finalizePD` does the proper translation, by taking
into account the platform, available dependencies, etc. and picks a
flag assignment (or gives an error if no flag assignment can be found)
b. `flattenPackageDescription` ignores flag assignment and just joins all
Expand Down

0 comments on commit 193f49d

Please sign in to comment.