1616-- Top level interface to dependency resolution.
1717{-# LANGUAGE LambdaCase #-}
1818{-# LANGUAGE FlexibleContexts #-}
19+ {-# LANGUAGE NamedFieldPuns #-}
1920module Distribution.Client.Dependency
2021 ( -- * The main package dependency resolver
2122 DepResolverParams
@@ -73,7 +74,7 @@ import Distribution.Client.Compat.Prelude
7374import Distribution.Client.Dependency.Types
7475 ( PackagesPreferenceDefault (.. )
7576 )
76- import Distribution.Client.SolverInstallPlan (SolverInstallPlan , SolverPlanIndex )
77+ import Distribution.Client.SolverInstallPlan (SolverInstallPlan )
7778import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
7879import Distribution.Client.Types
7980 ( AllowNewer (.. )
@@ -141,6 +142,7 @@ import qualified Distribution.Solver.Types.ComponentDeps as CD
141142import Distribution.Solver.Types.ConstraintSource
142143import Distribution.Solver.Types.DependencyResolver
143144import Distribution.Solver.Types.InstalledPreference as Preference
145+ import Distribution.Solver.Types.InstSolverPackage (InstSolverPackage (.. ))
144146import Distribution.Solver.Types.LabeledPackageConstraint
145147import Distribution.Solver.Types.OptionalStanza
146148import Distribution.Solver.Types.PackageConstraint
@@ -166,7 +168,6 @@ import Data.List
166168import qualified Data.Map as Map
167169import qualified Data.Set as Set
168170import Text.PrettyPrint hiding ((<>) )
169- import Data.Maybe (fromJust )
170171import GHC.Stack (HasCallStack )
171172import qualified Data.Tree
172173import qualified Data.Graph
@@ -787,6 +788,46 @@ resolveDependencies toolchains pkgConfigDB installedPkgIndex params = do
787788 preferences
788789 constraints
789790 targets
791+
792+ step $ render $ vcat
793+ [ text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
794+ , text " Solver plan"
795+ , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
796+ ]
797+ for_ pkgs $ \ pkg -> do
798+ step $ render $
799+ hang (pretty (solverQPN pkg) <+> text " ->" <+> pretty (solverId pkg)) 4 $ case pkg of
800+ PreExisting InstSolverPackage {instSolverPkgExeDeps, instSolverPkgLibDeps} ->
801+ vcat
802+ [ hang (pretty comp) 2 $ vcat
803+ [ vcat [ hang (text " lib-deps:" ) 2 (vcat (map pretty libDeps)) | not (null libDeps) ]
804+ , vcat [ hang (text " exe-deps:" ) 2 (vcat (map pretty exeDeps)) | not (null exeDeps) ]
805+ ]
806+ | (comp, (libDeps, exeDeps)) <- CD. toList (CD. zip instSolverPkgLibDeps instSolverPkgExeDeps)
807+ ]
808+ Configured SolverPackage {solverPkgExeDeps, solverPkgLibDeps} ->
809+ vcat
810+ [ hang (pretty comp) 2 $ vcat
811+ [ vcat [ hang (text " lib-deps:" ) 2 (vcat (map pretty libDeps)) | not (null libDeps) ]
812+ , vcat [ hang (text " exe-deps:" ) 2 (vcat (map pretty exeDeps)) | not (null exeDeps) ]
813+ ]
814+ | (comp, (libDeps, exeDeps)) <- CD. toList (CD. zip solverPkgLibDeps solverPkgExeDeps)
815+ ]
816+
817+ step $ render $ vcat
818+ [ text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
819+ , text " Scopes"
820+ , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
821+ , renderSolverPlanScopes pkgs
822+ ]
823+
824+ step $ render $ vcat
825+ [ text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
826+ , text " Dependency tree"
827+ , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
828+ , renderSolverPlanTree pkgs
829+ ]
830+
790831 validateSolverResult toolchains pkgs
791832 where
792833 installedPkgIndex' = Staged $ \ case
@@ -838,93 +879,30 @@ resolveDependencies toolchains pkgConfigDB installedPkgIndex params = do
838879 preferences :: PackageName -> PackagePreferences
839880 preferences = interpretPackagesPreference targets defpref prefs
840881
841- dumpResolverPackageIndex :: HasCallStack => [ResolverPackage UnresolvedPkgLoc ] -> Doc
842- dumpResolverPackageIndex pkgs =
843- vcat
844- [
845- text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
846- , text " Solver results"
847- , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
848- , vcat
849- [ text " -" <+> nest 2 (dumpResolverPackage pkg)
850- | pkg <- pkgs
851- ]
852- -- text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
853- -- , text "Library roots"
854- -- , text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
855- -- , vcat
856- -- [ text "-" <+> pretty root
857- -- | root <- SolverInstallPlan.libraryRoots g
858- -- ]
859- -- , hang (text "closure") 4 $
860- -- vcat $ map (pretty . Graph.nodeKey) $ fromJust $ Graph.closure g $ SolverInstallPlan.libraryRoots g
861- -- , hang (text "nonSetupClosure") 4 $
862- -- vcat $ map (pretty . Graph.nodeKey) $ Graph.toList $ SolverInstallPlan.nonSetupClosure g $ SolverInstallPlan.libraryRoots g
863- -- , text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
864- -- , text "Setup roots"
865- -- , text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
866- -- , vcat
867- -- [ hang (pretty i <> text ".") 4 $ vcat
868- -- [ hang (text "roots:") 4 $
869- -- vcat $ map pretty rootset'
870- -- , hang (text "closure:") 4 $
871- -- vcat $ map (pretty . Graph.nodeKey) $ fromJust $ Graph.closure g rootset'
872- -- , hang (text "nonSetupClosure:") 4 $
873- -- vcat $ map (pretty . Graph.nodeKey) $ Graph.toList $ SolverInstallPlan.nonSetupClosure g rootset'
874- -- ]
875- -- | (i, rootset) <- zip [1::Int ..] (SolverInstallPlan.setupRoots g)
876- -- , let rootset' = sort rootset
877- -- ]
878- -- , text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
879- -- , text "Scopes"
880- -- , text "~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
881- -- , vcat [ (pretty pp <+> text "/") $+$ nest 4 (vcat (map pretty (Set.toList sids)))
882- -- | (pp, sids) <- Map.toList (qualifications g)
883- -- ]
884- -- , vcat [ hang (pretty key) 4 (vcat [ text "-" <+> pretty n | n <- neigh]) | (_pkg, key, neigh) <- edges ]
885- , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
886- , text " Dependency tree"
887- , text " ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
888- , text (Data.Tree. drawForest dfs)
882+ renderSolverPlanScopes :: [SolverInstallPlan. SolverPlanPackage ] -> Doc
883+ renderSolverPlanScopes pkgs = vcat
884+ [ vcat [ (pretty pp <+> text " /" ) $+$ nest 4 (vcat (map pretty (Set. toList sids)))
885+ | (pp, sids) <- Map. toList (SolverInstallPlan. qualifications g)
886+ ]
887+ -- , vcat [ hang (pretty key) 4 (vcat [ text "-" <+> pretty n | n <- neigh]) | (_pkg, key, neigh) <- mapG ]
889888 ]
890- -- ]
891889 where
892- g :: SolverPlanIndex
893890 g = Graph. fromDistinctList pkgs
891+ -- (_g', mapG, _invG) = Data.Graph.graphFromEdges [ (pkg, Graph.nodeKey pkg, Graph.nodeNeighbors pkg) | pkg <- pkgs]
894892
895- (graphForward, graphVertexToNode, graphKeyToVertex) = Graph. toGraph g
896893
894+ renderSolverPlanTree :: HasCallStack => [SolverInstallPlan. SolverPlanPackage ] -> Doc
895+ renderSolverPlanTree pkgs = text (Data.Tree. drawForest dfs)
896+ where
897+ g = Graph. fromDistinctList pkgs
898+
899+ (graphForward, graphVertexToNode, graphKeyToVertex) = Graph. toGraph g
900+
897901 dfs = fmap (fmap (prettyShow . solverId . graphVertexToNode)) $ Data.Graph. dfs graphForward roots
902+
898903 Just roots = traverse graphKeyToVertex $ concat $ SolverInstallPlan. libraryRoots g : SolverInstallPlan. setupRoots g
899904
900905
901- dumpNodes :: SolverPlanIndex -> Doc
902- dumpNodes solverPlanIndex = vcat
903- [ hang (pretty node) 4 $
904- vcat [ hang (text " deps:" ) 4 $ vcat
905- [ pretty depid <+> (if solverStage node /= solverStage depid then text " WRONG" else mempty )
906- | depid <- map Graph. nodeKey deps
907- ]
908- | let deps = fromJust (Graph. neighbors solverPlanIndex node)
909- , not (null deps)
910- ]
911- $$
912- vcat [ hang (text " reverse-deps:" ) 4 $
913- vcat [ pretty rdepid <+> (if solverStage node /= solverStage rdepid then text " WRONG" else mempty )
914- | rdepid <- map Graph. nodeKey rdeps
915- ]
916- | let rdeps = fromJust (Graph. revNeighbors solverPlanIndex node)
917- , not (null rdeps)
918- ]
919- | node <- Graph. keys solverPlanIndex
920- ]
921-
922- drawForest :: Pretty a => [Data.Graph. Tree a ] -> Doc
923- drawForest = vcat . map drawTree
924-
925- drawTree :: Pretty a => Data.Graph. Tree a -> Doc
926- drawTree (Data.Graph. Node a ts0) = vcat [pretty a, nest 4 (vcat (map drawTree ts0))]
927-
928906-- | Give an interpretation to the global 'PackagesPreference' as
929907-- specific per-package 'PackageVersionPreference'.
930908interpretPackagesPreference
0 commit comments