Skip to content

Commit

Permalink
Add option to print dependencies as tree
Browse files Browse the repository at this point in the history
  • Loading branch information
akshaymankar committed Oct 4, 2018
1 parent a299ac6 commit a789ae5
Show file tree
Hide file tree
Showing 2 changed files with 65 additions and 9 deletions.
70 changes: 61 additions & 9 deletions src/Stack/Dot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module Stack.Dot (dot
) where

import qualified Data.Foldable as F
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.Text as Text
Expand Down Expand Up @@ -65,6 +66,8 @@ data ListDepsOpts = ListDepsOpts
-- ^ Separator between the package name and details.
, listDepsLicense :: !Bool
-- ^ Print dependency licenses instead of versions.
, listDepsTree :: !Bool
-- ^ Print dependency tree.
}

-- | Visualize the project's dependencies as a graphviz graph
Expand Down Expand Up @@ -132,15 +135,64 @@ listDependencies :: HasEnvConfig env
-> RIO env ()
listDependencies opts = do
let dotOpts = listDepsDotOpts opts
(_, resultGraph) <- createPrunedDependencyGraph dotOpts
void (Map.traverseWithKey go (snd <$> resultGraph))
where go name payload =
let payloadText =
if listDepsLicense opts
then maybe "<unknown>" (Text.pack . display . either licenseFromSPDX id) (payloadLicense payload)
else maybe "<unknown>" (Text.pack . show) (payloadVersion payload)
line = Text.pack (packageNameString name) <> listDepsSep opts <> payloadText
in liftIO $ Text.putStrLn line
(pkgs, resultGraph) <- createPrunedDependencyGraph dotOpts
if listDepsTree opts then
do
liftIO $ Text.putStrLn "Packages"
liftIO $ printTree opts 0 [] pkgs resultGraph
else
void (Map.traverseWithKey go (snd <$> resultGraph))
where go name payload = liftIO $ Text.putStrLn $ listDepsLine opts name payload

printTree :: ListDepsOpts
-> Int
-> [Int]
-> Set PackageName
-> Map PackageName (Set PackageName, DotPayload)
-> IO ()
printTree opts depth remainingDepsCounts packages dependencyMap =
F.sequence_ $ Seq.mapWithIndex go (toSeq packages)
where
toSeq = Seq.fromList . Set.toList
go index name = let newDepsCounts = remainingDepsCounts ++ [Set.size packages - index - 1]
(deps, payload) = (Map.!) dependencyMap name
in do
printTreeNode opts depth newDepsCounts deps payload name
if Just depth == dotDependencyDepth (listDepsDotOpts opts)
then return ()
else printTree opts (depth + 1) newDepsCounts deps dependencyMap

printTreeNode :: ListDepsOpts
-> Int
-> [Int]
-> Set PackageName
-> DotPayload
-> PackageName
-> IO ()
printTreeNode opts depth remainingDepsCounts deps payload name =
let remainingDepth = fromMaybe 999 (dotDependencyDepth (listDepsDotOpts opts)) - depth
hasDeps = not $ null deps
in Text.putStrLn $ treeNodePrefix "" remainingDepsCounts hasDeps remainingDepth <> " " <> listDepsLine opts name payload

treeNodePrefix :: Text -> [Int] -> Bool -> Int -> Text
treeNodePrefix t [] _ _ = t
treeNodePrefix t [0] True 0 = t <> "└──"
treeNodePrefix t [_] True 0 = t <> "├──"
treeNodePrefix t [0] True _ = t <> "└─┬"
treeNodePrefix t [_] True _ = t <> "├─┬"
treeNodePrefix t [0] False _ = t <> "└──"
treeNodePrefix t [_] False _ = t <> "├──"
treeNodePrefix t (0:ns) d remainingDepth = treeNodePrefix (t <> " ") ns d remainingDepth
treeNodePrefix t (_:ns) d remainingDepth = treeNodePrefix (t <> "") ns d remainingDepth

listDepsLine :: ListDepsOpts -> PackageName -> DotPayload -> Text
listDepsLine opts name payload = Text.pack (packageNameString name) <> listDepsSep opts <> payloadText opts payload

payloadText :: ListDepsOpts -> DotPayload -> Text
payloadText opts payload =
if listDepsLicense opts
then maybe "<unknown>" (Text.pack . display . either licenseFromSPDX id) (payloadLicense payload)
else maybe "<unknown>" (Text.pack . show) (payloadVersion payload)

-- | @pruneGraph dontPrune toPrune graph@ prunes all packages in
-- @graph@ with a name in @toPrune@ and removes resulting orphans
Expand Down
4 changes: 4 additions & 0 deletions src/Stack/Options/DotParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,4 +67,8 @@ listDepsOptsParser = ListDepsOpts
"license"
"printing of dependency licenses instead of versions"
idm
<*> boolFlags False
"tree"
"printing of dependencies as a tree"
idm
where escapeSep sep = T.replace "\\t" "\t" (T.replace "\\n" "\n" sep)

0 comments on commit a789ae5

Please sign in to comment.