Skip to content

Commit

Permalink
Add field names to ConfiguredPackage.
Browse files Browse the repository at this point in the history
Signed-off-by: Edward Z. Yang <[email protected]>
  • Loading branch information
ezyang committed Apr 3, 2016
1 parent f5526eb commit bc0080f
Show file tree
Hide file tree
Showing 7 changed files with 29 additions and 33 deletions.
8 changes: 4 additions & 4 deletions cabal-install/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -228,8 +228,8 @@ configureSetupScript packageDBs

explicitSetupDeps :: Maybe [(UnitId, PackageId)]
explicitSetupDeps = do
ReadyPackage (ConfiguredPackage (SourcePackage _ gpkg _ _) _ _ _) deps
<- mpkg
ReadyPackage cpkg deps <- mpkg
let gpkg = packageDescription (confPkgSource cpkg)
-- Check if there is an explicit setup stanza
_buildInfo <- PkgDesc.setupBuildInfo (PkgDesc.packageDescription gpkg)
-- Return the setup dependencies computed by the solver
Expand Down Expand Up @@ -348,15 +348,15 @@ configurePackage :: Verbosity
-> [String]
-> IO ()
configurePackage verbosity platform comp scriptOptions configFlags
(ReadyPackage (ConfiguredPackage (SourcePackage _ gpkg _ _)
flags stanzas _)
(ReadyPackage (ConfiguredPackage spkg flags stanzas _)
deps)
extraArgs =

setupWrapper verbosity
scriptOptions (Just pkg) configureCommand configureFlags extraArgs

where
gpkg = packageDescription spkg
configureFlags = filterConfigureFlags configFlags {
configConfigurationsFlags = flags,
-- We generate the legacy constraints as well as the new style precise
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ instance PackageSourceDeps InstalledPackageEx where
sourceDeps (InstalledPackageEx _ _ deps) = deps

instance PackageSourceDeps (ConfiguredPackage loc) where
sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId $ CD.nonSetupDeps deps
sourceDeps cpkg = map confSrcId $ CD.nonSetupDeps (confPkgDeps cpkg)

instance PackageSourceDeps InstalledPackage where
sourceDeps (InstalledPackage _ deps) = deps
Expand Down
4 changes: 2 additions & 2 deletions cabal-install/Distribution/Client/Fetch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -138,8 +138,8 @@ planPackages verbosity comp platform fetchFlags
-- The packages we want to fetch are those packages the 'InstallPlan'
-- that are in the 'InstallPlan.Configured' state.
return
[ pkg
| (InstallPlan.Configured (ConfiguredPackage pkg _ _ _))
[ confPkgSource cpkg
| (InstallPlan.Configured cpkg)
<- InstallPlan.toList installPlan ]

| otherwise =
Expand Down
20 changes: 8 additions & 12 deletions cabal-install/Distribution/Client/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -537,9 +537,8 @@ checkPrintPlan verbosity installed installPlan sourcePkgDb
-- are already fetched.
let offline = fromFlagOrDefault False (installOfflineMode installFlags)
when offline $ do
let pkgs = [ sourcePkg
| InstallPlan.Configured (ConfiguredPackage sourcePkg _ _ _)
<- InstallPlan.toList installPlan ]
let pkgs = [ confPkgSource cpkg
| InstallPlan.Configured cpkg <- InstallPlan.toList installPlan ]
notFetched <- fmap (map packageInfoId)
. filterM (fmap isNothing . checkFetched . packageSource)
$ pkgs
Expand Down Expand Up @@ -652,7 +651,7 @@ printPlan dryRun verbosity plan sourcePkgDb = case plan of
showPkgAndReason (ReadyPackage pkg' _, pr) = display (packageId pkg') ++
showLatest pkg' ++
showFlagAssignment (nonDefaultFlags pkg') ++
showStanzas (stanzas pkg') ++
showStanzas (confPkgStanzas pkg') ++
showDep pkg' ++
case pr of
NewPackage -> " (new package)"
Expand Down Expand Up @@ -681,14 +680,11 @@ printPlan dryRun verbosity plan sourcePkgDb = case plan of
toFlagAssignment = map (\ f -> (flagName f, flagDefault f))

nonDefaultFlags :: ConfiguredPackage loc -> FlagAssignment
nonDefaultFlags (ConfiguredPackage spkg fa _ _) =
nonDefaultFlags cpkg =
let defaultAssignment =
toFlagAssignment
(genPackageFlags (Source.packageDescription spkg))
in fa \\ defaultAssignment

stanzas :: ConfiguredPackage loc -> [OptionalStanza]
stanzas (ConfiguredPackage _ _ sts _) = sts
(genPackageFlags (Source.packageDescription (confPkgSource cpkg)))
in confPkgFlags cpkg \\ defaultAssignment

showStanzas :: [OptionalStanza] -> String
showStanzas = concatMap ((' ' :) . showStanza)
Expand Down Expand Up @@ -1025,7 +1021,7 @@ updateSandboxTimestampsFile (UseSandbox sandboxDir)
withUpdateTimestamps sandboxDir (compilerId comp) platform $ \_ -> do
let allInstalled = [ pkg | InstallPlan.Installed pkg _ _
<- InstallPlan.toList installPlan ]
allSrcPkgs = [ pkg | ReadyPackage (ConfiguredPackage pkg _ _ _) _
allSrcPkgs = [ confPkgSource cpkg | ReadyPackage cpkg _
<- allInstalled ]
allPaths = [ pth | LocalUnpackedPackage pth
<- map packageSource allSrcPkgs]
Expand Down Expand Up @@ -1412,7 +1408,7 @@ installUnpackedPackage verbosity buildLimit installLock numJobs
writeFileAtomic descFilePath pkgtxt

-- Compute the IPID
let flags (ReadyPackage (ConfiguredPackage _ x _ _) _) = x
let flags (ReadyPackage cpkg _) = confPkgFlags cpkg
pkg_name = pkgName (PackageDescription.package pkg)
cid = Configure.computeComponentId Cabal.NoFlag
(PackageDescription.package pkg) (CLibName (display pkg_name))
Expand Down
2 changes: 1 addition & 1 deletion cabal-install/Distribution/Client/InstallSymlink.hs
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ symlinkBinaries platform comp configFlags installFlags plan =
then return Nothing
else return (Just (pkgid, publicExeName,
privateBinDir </> privateExeName))
| (ReadyPackage (ConfiguredPackage _ _flags _ _) _, pkg, exe) <- exes
| (ReadyPackage _cpkg _, pkg, exe) <- exes
, let pkgid = packageId pkg
-- This is a bit dodgy; probably won't work for Backpack packages
ipid = fakeUnitId pkgid
Expand Down
22 changes: 11 additions & 11 deletions cabal-install/Distribution/Client/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,23 +112,23 @@ fakeUnitId = mkUnitId . (".fake."++) . display
-- the sense that it provides all the configuration information and so the
-- final configure process will be independent of the environment.
--
data ConfiguredPackage loc = ConfiguredPackage
(SourcePackage loc) -- package info, including repo
FlagAssignment -- complete flag assignment for the package
[OptionalStanza] -- list of enabled optional stanzas for the package
(ComponentDeps [ConfiguredId])
data ConfiguredPackage loc = ConfiguredPackage {
confPkgSource :: SourcePackage loc, -- package info, including repo
confPkgFlags :: FlagAssignment, -- complete flag assignment for the package
confPkgStanzas :: [OptionalStanza], -- list of enabled optional stanzas for the package
confPkgDeps :: ComponentDeps [ConfiguredId]
-- set of exact dependencies (installed or source).
-- These must be consistent with the 'buildDepends'
-- in the 'PackageDescription' that you'd get by
-- applying the flag assignment and optional stanzas.
}
deriving (Eq, Show, Generic)

instance Binary loc => Binary (ConfiguredPackage loc)
instance (Binary loc) => Binary (ConfiguredPackage loc)

-- | A ConfiguredId is a package ID for a configured package.
--
-- Once we configure a source package we know it's UnitId
-- (at least, in principle, even if we have to fake it currently). It is still
-- Once we configure a source package we know it's UnitId. It is still
-- however useful in lots of places to also know the source ID for the package.
-- We therefore bundle the two.
--
Expand All @@ -155,13 +155,13 @@ instance HasUnitId ConfiguredId where
installedUnitId = confInstId

instance Package (ConfiguredPackage loc) where
packageId (ConfiguredPackage pkg _ _ _) = packageId pkg
packageId cpkg = packageId (confPkgSource cpkg)

instance PackageFixedDeps (ConfiguredPackage loc) where
depends (ConfiguredPackage _ _ _ deps) = fmap (map confInstId) deps
depends cpkg = fmap (map installedUnitId) (confPkgDeps cpkg)

instance HasUnitId (ConfiguredPackage loc) where
installedUnitId = fakeUnitId . packageId
installedUnitId cpkg = fakeUnitId (packageId cpkg)

-- | Like 'ConfiguredPackage', but with all dependencies guaranteed to be
-- installed already, hence itself ready to be installed.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -430,9 +430,9 @@ extractInstallPlan = catMaybes . map confPkg . CI.InstallPlan.toList
confPkg _ = Nothing

srcPkg :: ConfiguredPackage UnresolvedPkgLoc -> (String, Int)
srcPkg (ConfiguredPackage pkg _flags _stanzas _deps) =
srcPkg cpkg =
let C.PackageIdentifier (C.PackageName p) (Version (n:_) _) =
packageInfoId pkg
packageInfoId (confPkgSource cpkg)
in (p, n)

{-------------------------------------------------------------------------------
Expand Down

0 comments on commit bc0080f

Please sign in to comment.