From 1effd34bdb5507c29f6fcae70825d5126627c2cf Mon Sep 17 00:00:00 2001 From: Edsko de Vries <edsko@well-typed.com> Date: Mon, 30 Mar 2015 16:41:14 +0100 Subject: [PATCH] Add ComponentSetup to ComponentDeps Although we don't use the new setup dependency component anywhere yet, I've replaced all uses of CD.flatDeps with CD.nonSetupDeps. This means that when we do introduce the setup dependencies, all code in Cabal will still use all dependencies except the setup dependencies, just like now. In other words, using the setup dependencies in some places would be a conscious decision; the default is that we leave the behaviour unchanged. --- .../Client/BuildReports/Storage.hs | 4 +-- .../Distribution/Client/ComponentDeps.hs | 29 +++++++++++++++++++ .../Distribution/Client/Configure.hs | 4 +-- .../Modular/ConfiguredConversion.hs | 2 +- .../Client/Dependency/TopDown/Types.hs | 4 +-- cabal-install/Distribution/Client/Install.hs | 8 ++--- .../Distribution/Client/InstallPlan.hs | 6 ++-- .../Distribution/Client/InstallSymlink.hs | 2 +- .../Distribution/Client/PlanIndex.hs | 14 ++++----- cabal-install/Distribution/Client/Types.hs | 2 +- 10 files changed, 52 insertions(+), 23 deletions(-) diff --git a/cabal-install/Distribution/Client/BuildReports/Storage.hs b/cabal-install/Distribution/Client/BuildReports/Storage.hs index a64bf9068a..a4f20de32d 100644 --- a/cabal-install/Distribution/Client/BuildReports/Storage.hs +++ b/cabal-install/Distribution/Client/BuildReports/Storage.hs @@ -130,13 +130,13 @@ fromPlanPackage :: Platform -> CompilerId fromPlanPackage (Platform arch os) comp planPackage = case planPackage of InstallPlan.Installed (ReadyPackage srcPkg flags _ deps) result -> Just $ ( BuildReport.new os arch comp - (packageId srcPkg) flags (map packageId (CD.flatDeps deps)) + (packageId srcPkg) flags (map packageId (CD.nonSetupDeps deps)) (Right result) , extractRepo srcPkg) InstallPlan.Failed (ConfiguredPackage srcPkg flags _ deps) result -> Just $ ( BuildReport.new os arch comp - (packageId srcPkg) flags (map confSrcId (CD.flatDeps deps)) + (packageId srcPkg) flags (map confSrcId (CD.nonSetupDeps deps)) (Left result) , extractRepo srcPkg ) diff --git a/cabal-install/Distribution/Client/ComponentDeps.hs b/cabal-install/Distribution/Client/ComponentDeps.hs index f6ee4d9a77..ef38a25148 100644 --- a/cabal-install/Distribution/Client/ComponentDeps.hs +++ b/cabal-install/Distribution/Client/ComponentDeps.hs @@ -21,10 +21,15 @@ module Distribution.Client.ComponentDeps ( , singleton , insert , fromLibraryDeps + , fromSetupDeps , fromInstalled -- ** Deconstructing ComponentDeps , toList , flatDeps + , nonSetupDeps + , libraryDeps + , setupDeps + , select ) where import Data.Map (Map) @@ -47,6 +52,7 @@ data Component = | ComponentExe String | ComponentTest String | ComponentBench String + | ComponentSetup deriving (Show, Eq, Ord) -- | Dependency for a single component @@ -91,6 +97,10 @@ insert comp a = ComponentDeps . Map.alter aux comp . unComponentDeps fromLibraryDeps :: a -> ComponentDeps a fromLibraryDeps = singleton ComponentLib +-- | ComponentDeps containing setup dependencies only +fromSetupDeps :: a -> ComponentDeps a +fromSetupDeps = singleton ComponentSetup + -- | ComponentDeps for installed packages -- -- We assume that installed packages only record their library dependencies @@ -111,3 +121,22 @@ toList = Map.toList . unComponentDeps -- @#ifdef@s for 7.10 just for the use of 'fold'. flatDeps :: Monoid a => ComponentDeps a -> a flatDeps = fold + +-- | All dependencies except the setup dependencies +-- +-- Prior to the introduction of setup dependencies (TODO: Version? 1.23) this +-- would have been _all_ dependencies +nonSetupDeps :: Monoid a => ComponentDeps a -> a +nonSetupDeps = select (/= ComponentSetup) + +-- | Library dependencies proper only +libraryDeps :: Monoid a => ComponentDeps a -> a +libraryDeps = select (== ComponentLib) + +-- | Setup dependencies +setupDeps :: Monoid a => ComponentDeps a -> a +setupDeps = select (== ComponentSetup) + +-- | Select dependencies satisfying a given predicate +select :: Monoid a => (Component -> Bool) -> ComponentDeps a -> a +select p = foldMap snd . filter (p . fst) . toList diff --git a/cabal-install/Distribution/Client/Configure.hs b/cabal-install/Distribution/Client/Configure.hs index aa0d610d09..aadf36a131 100644 --- a/cabal-install/Distribution/Client/Configure.hs +++ b/cabal-install/Distribution/Client/Configure.hs @@ -237,10 +237,10 @@ configurePackage verbosity platform comp scriptOptions configFlags -- deps. In the end only one set gets passed to Setup.hs configure, -- depending on the Cabal version we are talking to. configConstraints = [ thisPackageVersion (packageId deppkg) - | deppkg <- CD.flatDeps deps ], + | deppkg <- CD.nonSetupDeps deps ], configDependencies = [ (packageName (Installed.sourcePackageId deppkg), Installed.installedPackageId deppkg) - | deppkg <- CD.flatDeps deps ], + | deppkg <- CD.nonSetupDeps deps ], -- Use '--exact-configuration' if supported. configExactConfiguration = toFlag True, configVerbosity = toFlag verbosity, diff --git a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs index 8a5d4b6060..47968d19ec 100644 --- a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs +++ b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs @@ -28,7 +28,7 @@ convCP iidx sidx (CP qpi fa es ds) = case convPI qpi of Left pi -> PreExisting $ InstalledPackage (fromJust $ SI.lookupInstalledPackageId iidx pi) - (map confSrcId $ CD.flatDeps ds') + (map confSrcId $ CD.nonSetupDeps ds') Right pi -> Configured $ ConfiguredPackage (fromJust $ CI.lookupPackageId sidx pi) fa diff --git a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs index 6f31385994..73c1a27327 100644 --- a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs +++ b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs @@ -115,10 +115,10 @@ instance PackageSourceDeps InstalledPackageEx where sourceDeps (InstalledPackageEx _ _ deps) = deps instance PackageSourceDeps ConfiguredPackage where - sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId $ CD.flatDeps deps + sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId $ CD.nonSetupDeps deps instance PackageSourceDeps ReadyPackage where - sourceDeps (ReadyPackage _ _ _ deps) = map packageId $ CD.flatDeps deps + sourceDeps (ReadyPackage _ _ _ deps) = map packageId $ CD.nonSetupDeps deps instance PackageSourceDeps InstalledPackage where sourceDeps (InstalledPackage _ deps) = deps diff --git a/cabal-install/Distribution/Client/Install.hs b/cabal-install/Distribution/Client/Install.hs index 568d722c26..81a990cb40 100644 --- a/cabal-install/Distribution/Client/Install.hs +++ b/cabal-install/Distribution/Client/Install.hs @@ -564,8 +564,8 @@ packageStatus _comp installedPkgIndex cpkg = -> [MergeResult PackageIdentifier PackageIdentifier] changes pkg pkg' = filter changed $ mergeBy (comparing packageName) - (resolveInstalledIds $ Installed.depends pkg) -- deps of installed pkg - (resolveInstalledIds $ CD.flatDeps (depends pkg')) -- deps of configured pkg + (resolveInstalledIds $ Installed.depends pkg) -- deps of installed pkg + (resolveInstalledIds $ CD.nonSetupDeps (depends pkg')) -- deps of configured pkg -- convert to source pkg ids via index resolveInstalledIds :: [InstalledPackageId] -> [PackageIdentifier] @@ -1192,10 +1192,10 @@ installReadyPackage platform cinfo configFlags -- In the end only one set gets passed to Setup.hs configure, depending on -- the Cabal version we are talking to. configConstraints = [ thisPackageVersion (packageId deppkg) - | deppkg <- CD.flatDeps deps ], + | deppkg <- CD.nonSetupDeps deps ], configDependencies = [ (packageName (Installed.sourcePackageId deppkg), Installed.installedPackageId deppkg) - | deppkg <- CD.flatDeps deps ], + | deppkg <- CD.nonSetupDeps deps ], -- Use '--exact-configuration' if supported. configExactConfiguration = toFlag True, configBenchmarks = toFlag False, diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs index 50e593e955..d345b011a9 100644 --- a/cabal-install/Distribution/Client/InstallPlan.hs +++ b/cabal-install/Distribution/Client/InstallPlan.hs @@ -495,7 +495,7 @@ problems platform cinfo fakeMap indepGoals index = ++ [ PackageStateInvalid pkg pkg' | pkg <- PackageIndex.allPackages index - , Just pkg' <- map (PlanIndex.fakeLookupInstalledPackageId fakeMap index) (CD.flatDeps (depends pkg)) + , Just pkg' <- map (PlanIndex.fakeLookupInstalledPackageId fakeMap index) (CD.nonSetupDeps (depends pkg)) , not (stateDependencyRelation pkg pkg') ] -- | The graph of packages (nodes) and dependencies (edges) must be acyclic. @@ -616,7 +616,7 @@ configuredPackageProblems platform cinfo ++ [ MissingFlag flag | OnlyInLeft flag <- mergedFlags ] ++ [ ExtraFlag flag | OnlyInRight flag <- mergedFlags ] ++ [ DuplicateDeps pkgs - | pkgs <- CD.flatDeps (fmap (duplicatesBy (comparing packageName)) specifiedDeps) ] + | pkgs <- CD.nonSetupDeps (fmap (duplicatesBy (comparing packageName)) specifiedDeps) ] ++ [ MissingDep dep | OnlyInLeft dep <- mergedDeps ] ++ [ ExtraDep pkgid | OnlyInRight pkgid <- mergedDeps ] ++ [ InvalidDep dep pkgid | InBoth dep pkgid <- mergedDeps @@ -637,7 +637,7 @@ configuredPackageProblems platform cinfo dependencyName (Dependency name _) = name mergedDeps :: [MergeResult Dependency PackageId] - mergedDeps = mergeDeps requiredDeps (CD.flatDeps specifiedDeps) + mergedDeps = mergeDeps requiredDeps (CD.nonSetupDeps specifiedDeps) mergeDeps :: [Dependency] -> [PackageId] -> [MergeResult Dependency PackageId] mergeDeps required specified = diff --git a/cabal-install/Distribution/Client/InstallSymlink.hs b/cabal-install/Distribution/Client/InstallSymlink.hs index dffc8321ca..0ea1921688 100644 --- a/cabal-install/Distribution/Client/InstallSymlink.hs +++ b/cabal-install/Distribution/Client/InstallSymlink.hs @@ -123,7 +123,7 @@ symlinkBinaries comp configFlags installFlags plan = | (ReadyPackage _ _flags _ deps, pkg, exe) <- exes , let pkgid = packageId pkg pkg_key = mkPackageKey (packageKeySupported comp) pkgid - (map Installed.packageKey (CD.flatDeps deps)) [] + (map Installed.packageKey (CD.nonSetupDeps deps)) [] publicExeName = PackageDescription.exeName exe privateExeName = prefix ++ publicExeName ++ suffix prefix = substTemplate pkgid pkg_key prefixTemplate diff --git a/cabal-install/Distribution/Client/PlanIndex.hs b/cabal-install/Distribution/Client/PlanIndex.hs index 16813b4849..d98d3b9963 100644 --- a/cabal-install/Distribution/Client/PlanIndex.hs +++ b/cabal-install/Distribution/Client/PlanIndex.hs @@ -111,7 +111,7 @@ brokenPackages fakeMap index = [ (pkg, missing) | pkg <- allPackages index , let missing = - [ pkg' | pkg' <- CD.flatDeps (depends pkg) + [ pkg' | pkg' <- CD.nonSetupDeps (depends pkg) , isNothing (fakeLookupInstalledPackageId fakeMap index pkg') ] , not (null missing) ] @@ -188,7 +188,7 @@ dependencyInconsistencies' fakeMap index = | -- For each package @pkg@ pkg <- allPackages index -- Find out which @ipid@ @pkg@ depends on - , ipid <- CD.flatDeps (fakeDepends fakeMap pkg) + , ipid <- CD.nonSetupDeps (fakeDepends fakeMap pkg) -- And look up those @ipid@ (i.e., @ipid@ is the ID of @dep@) , Just dep <- [fakeLookupInstalledPackageId fakeMap index ipid] ] @@ -204,8 +204,8 @@ dependencyInconsistencies' fakeMap index = reallyIsInconsistent [p1, p2] = let pid1 = installedPackageId p1 pid2 = installedPackageId p2 - in Map.findWithDefault pid1 pid1 fakeMap `notElem` CD.flatDeps (fakeDepends fakeMap p2) - && Map.findWithDefault pid2 pid2 fakeMap `notElem` CD.flatDeps (fakeDepends fakeMap p1) + in Map.findWithDefault pid1 pid1 fakeMap `notElem` CD.nonSetupDeps (fakeDepends fakeMap p2) + && Map.findWithDefault pid2 pid2 fakeMap `notElem` CD.nonSetupDeps (fakeDepends fakeMap p1) reallyIsInconsistent _ = True @@ -225,7 +225,7 @@ dependencyCycles :: (PackageFixedDeps pkg, HasInstalledPackageId pkg) dependencyCycles fakeMap index = [ vs | Graph.CyclicSCC vs <- Graph.stronglyConnComp adjacencyList ] where - adjacencyList = [ (pkg, installedPackageId pkg, CD.flatDeps (fakeDepends fakeMap pkg)) + adjacencyList = [ (pkg, installedPackageId pkg, CD.nonSetupDeps (fakeDepends fakeMap pkg)) | pkg <- allPackages index ] @@ -256,7 +256,7 @@ dependencyClosure fakeMap index pkgids0 = case closure mempty [] pkgids0 of Just _ -> closure completed failed pkgids Nothing -> closure completed' failed pkgids' where completed' = insert pkg completed - pkgids' = CD.flatDeps (depends pkg) ++ pkgids + pkgids' = CD.nonSetupDeps (depends pkg) ++ pkgids topologicalOrder :: (PackageFixedDeps pkg, HasInstalledPackageId pkg) @@ -322,5 +322,5 @@ dependencyGraph fakeMap index = (graph, vertexToPkg, idToVertex) resolve pid = Map.findWithDefault pid pid fakeMap edgesFrom pkg = ( () , resolve (installedPackageId pkg) - , CD.flatDeps (fakeDepends fakeMap pkg) + , CD.nonSetupDeps (fakeDepends fakeMap pkg) ) diff --git a/cabal-install/Distribution/Client/Types.hs b/cabal-install/Distribution/Client/Types.hs index 1c349b84ce..cf98026107 100644 --- a/cabal-install/Distribution/Client/Types.hs +++ b/cabal-install/Distribution/Client/Types.hs @@ -154,7 +154,7 @@ instance HasInstalledPackageId ReadyPackage where readyPackageKey :: Compiler -> ReadyPackage -> PackageKey readyPackageKey comp (ReadyPackage pkg _ _ deps) = mkPackageKey (packageKeySupported comp) (packageId pkg) - (map Info.packageKey (CD.flatDeps deps)) [] + (map Info.packageKey (CD.nonSetupDeps deps)) [] -- | Sometimes we need to convert a 'ReadyPackage' back to a -- GitLab