Skip to content
Snippets Groups Projects
Commit a53ea55c authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing: Committed by GitHub
Browse files

Fix (exe-)depends in plan.json (#3711)

* Properly render both depends and exe-depends in components. (by @ezyang)
* Import ComponentDeps qualified to avoid clashes
* Make ComponentDeps.zip compatible with containers<0.5
parent 4a9f11e6
No related branches found
No related tags found
No related merge requests found
......@@ -81,11 +81,12 @@ encodePlanAsJson elaboratedInstallPlan _elaboratedSharedConfig =
ElabPackage pkg ->
let components = J.object $
[ comp2str c J..= J.object
[ "depends" J..= map (jdisplay . confInstId) v ]
| (c,v) <- ComponentDeps.toList (pkgLibDependencies pkg) ] ++
[ comp2str c J..= J.object
[ "exe-depends" J..= map (jdisplay . confInstId) v ]
| (c,v) <- ComponentDeps.toList (pkgExeDependencies pkg) ]
[ "depends" J..= map (jdisplay . confInstId) ldeps
, "exe-depends" J..= map (jdisplay . confInstId) edeps ]
| (c,(ldeps,edeps))
<- ComponentDeps.toList $
ComponentDeps.zip (pkgLibDependencies pkg)
(pkgExeDependencies pkg) ]
in ["components" J..= components]
ElabComponent _ ->
["depends" J..= map (jdisplay . confInstId) (elabLibDependencies elab)
......
......@@ -22,6 +22,7 @@ module Distribution.Solver.Types.ComponentDeps (
, fromList
, singleton
, insert
, zip
, filterDeps
, fromLibraryDeps
, fromSetupDeps
......@@ -35,6 +36,7 @@ module Distribution.Solver.Types.ComponentDeps (
, select
) where
import Prelude hiding (zip)
import Data.Map (Map)
import qualified Data.Map as Map
import Distribution.Compat.Binary (Binary)
......@@ -119,6 +121,28 @@ insert comp a = ComponentDeps . Map.alter aux comp . unComponentDeps
aux Nothing = Just a
aux (Just a') = Just $ a `mappend` a'
-- | Zip two 'ComponentDeps' together by 'Component', using 'mempty'
-- as the neutral element when a 'Component' is present only in one.
zip :: (Monoid a, Monoid b) => ComponentDeps a -> ComponentDeps b -> ComponentDeps (a, b)
{- TODO/FIXME: Once we can expect containers>=0.5, switch to the more efficient version below:
zip (ComponentDeps d1) (ComponentDeps d2) =
ComponentDeps $
Map.mergeWithKey
(\_ a b -> Just (a,b))
(fmap (\a -> (a, mempty)))
(fmap (\b -> (mempty, b)))
d1 d2
-}
zip (ComponentDeps d1) (ComponentDeps d2) =
ComponentDeps $
Map.unionWith
mappend
(Map.map (\a -> (a, mempty)) d1)
(Map.map (\b -> (mempty, b)) d2)
-- | Keep only selected components (and their associated deps info).
filterDeps :: (Component -> a -> Bool) -> ComponentDeps a -> ComponentDeps a
filterDeps p = ComponentDeps . Map.filterWithKey p . unComponentDeps
......
......@@ -11,7 +11,7 @@ import qualified Distribution.Compat.Graph as Graph
import Distribution.Compat.Graph (IsNode(..))
import Distribution.Solver.Types.Settings
import Distribution.Solver.Types.PackageFixedDeps
import Distribution.Solver.Types.ComponentDeps as CD
import qualified Distribution.Solver.Types.ComponentDeps as CD
import Distribution.Client.Types
import Distribution.Client.JobControl
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment