Skip to content
Snippets Groups Projects
Commit e8d17565 authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Add more docs/comments to recently added utils

parent 377cc8f3
No related branches found
No related tags found
No related merge requests found
......@@ -65,6 +65,10 @@ instance Binary Component
type ComponentDep a = (Component, a)
-- | Fine-grained dependencies for a package
--
-- Typically used as @ComponentDeps [Dependency]@, to represent the list of
-- dependencies for each named component within a package.
--
newtype ComponentDeps a = ComponentDeps { unComponentDeps :: Map Component a }
deriving (Show, Functor, Eq, Ord, Generic)
......@@ -101,6 +105,7 @@ insert comp a = ComponentDeps . Map.alter aux comp . unComponentDeps
aux Nothing = Just a
aux (Just a') = Just $ a `mappend` a'
-- | Keep only selected components (and their associated deps info).
filterDeps :: (Component -> a -> Bool) -> ComponentDeps a -> ComponentDeps a
filterDeps p = ComponentDeps . Map.filterWithKey p . unComponentDeps
......
......@@ -188,13 +188,19 @@ data GenericInstallPlan ipkg srcpkg iresult ifailure = GenericInstallPlan {
planFakeMap :: !FakeMap,
planIndepGoals :: !Bool,
-- cached (lazily) graph
-- | Cached (lazily) graph
--
-- The 'Graph' representaion works in terms of integer node ids, so we
-- have to keep mapping to and from our meaningful nodes, which of course
-- are package ids.
--
planGraph :: Graph,
planGraphRev :: Graph,
planPkgIdOf :: Graph.Vertex -> UnitId,
planVertexOf :: UnitId -> Graph.Vertex
planGraphRev :: Graph, -- ^ Reverse deps, transposed
planPkgIdOf :: Graph.Vertex -> UnitId, -- ^ mapping back to package ids
planVertexOf :: UnitId -> Graph.Vertex -- ^ mapping into node ids
}
-- | Much like 'planPkgIdOf', but mapping back to full packages.
planPkgOf :: GenericInstallPlan ipkg srcpkg iresult ifailure
-> Graph.Vertex
-> GenericPlanPackage ipkg srcpkg iresult ifailure
......@@ -221,6 +227,8 @@ invariant plan =
(planIndepGoals plan)
(planIndex plan)
-- | Smart constructor that deals with caching the 'Graph' representation.
--
mkInstallPlan :: (HasUnitId ipkg, PackageFixedDeps ipkg,
HasUnitId srcpkg, PackageFixedDeps srcpkg)
=> PlanIndex ipkg srcpkg iresult ifailure
......@@ -233,6 +241,7 @@ mkInstallPlan index fakeMap indepGoals =
planFakeMap = fakeMap,
planIndepGoals = indepGoals,
-- lazily cache the graph stuff:
planGraph = graph,
planGraphRev = Graph.transposeG graph,
planPkgIdOf = vertexToPkgId,
......
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