Skip to content
Snippets Groups Projects
Commit 8f292660 authored by stuebinm's avatar stuebinm
Browse files

add dot language output for repository map graphs

parent 09f6bbda
No related branches found
No related tags found
No related merge requests found
Pipeline #13685 passed
...@@ -25,7 +25,7 @@ import Data.Maybe (isJust, mapMaybe) ...@@ -25,7 +25,7 @@ import Data.Maybe (isJust, mapMaybe)
import Data.Text (Text, isInfixOf) import Data.Text (Text, isInfixOf)
import qualified Data.Text as T import qualified Data.Text as T
import Dirgraph (graphToDot, invertGraph, resultToGraph, import Dirgraph (graphToDot, invertGraph, resultToGraph,
unreachableFrom) takeSubGraph, unreachableFrom)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import LintConfig (LintConfig', configMaxLintLevel) import LintConfig (LintConfig', configMaxLintLevel)
import Paths (normalise, normaliseWithFrag) import Paths (normalise, normaliseWithFrag)
...@@ -107,7 +107,7 @@ instance ToJSON DirResult where ...@@ -107,7 +107,7 @@ instance ToJSON DirResult where
. M.toList . M.toList
$ dirresultMaps res) $ dirresultMaps res)
-- unused in the hub, temporarily removed to make the output smaller -- unused in the hub, temporarily removed to make the output smaller
-- , "exitGraph" .= showDot (dirresultGraph res) , "exitGraph" .= showDot (dirresultGraph res)
] ]
, "severity" .= maximumLintLevel res , "severity" .= maximumLintLevel res
, "mapInfo" .= fmap (\tm -> A.object [ "badges" .= mapresultBadges tm ]) , "mapInfo" .= fmap (\tm -> A.object [ "badges" .= mapresultBadges tm ])
...@@ -178,7 +178,10 @@ recursiveCheckDir config prefix root = do ...@@ -178,7 +178,10 @@ recursiveCheckDir config prefix root = do
pure $ DirResult { dirresultDeps = missingDeps root maps' pure $ DirResult { dirresultDeps = missingDeps root maps'
, dirresultMissingAssets = mAssets , dirresultMissingAssets = mAssets
, dirresultMaps = maps' , dirresultMaps = maps'
, dirresultGraph = graphToDot exitGraph , dirresultGraph =
graphToDot
. takeSubGraph 7 root
$ exitGraph
} }
......
...@@ -5,19 +5,22 @@ ...@@ -5,19 +5,22 @@
module Dirgraph where module Dirgraph where
import CheckMap (MapResult (mapresultDepends)) import CheckMap (MapResult (mapresultDepends))
import Control.Monad (forM_) import Control.Monad (forM_, unless)
import Data.Functor ((<&>)) import Data.Functor ((<&>))
import Data.Map.Strict (Map, mapMaybeWithKey, mapWithKey, import Data.Map.Strict (Map, mapMaybeWithKey, mapWithKey,
traverseWithKey) traverseMaybeWithKey, traverseWithKey)
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Data.Set (Set, (\\)) import Data.Maybe (fromMaybe)
import qualified Data.Set as S import Data.Set (Set, (\\))
import Paths (normalise) import qualified Data.Set as S
import Text.Dot (Dot, (.->.)) import Paths (normalise)
import qualified Text.Dot as D import qualified System.FilePath as FP
import Types (Dep (LocalMap)) import System.FilePath.Posix (takeDirectory, (</>))
import Witherable (mapMaybe) import Text.Dot (Dot, (.->.))
import qualified Text.Dot as D
import Types (Dep (LocalMap))
import Witherable (mapMaybe)
-- | a simple directed graph -- | a simple directed graph
type Graph a = Map a (Set a) type Graph a = Map a (Set a)
...@@ -27,9 +30,11 @@ nodes = M.keysSet ...@@ -27,9 +30,11 @@ nodes = M.keysSet
-- | simple directed graph of exits -- | simple directed graph of exits
resultToGraph :: Map FilePath MapResult -> Graph FilePath resultToGraph :: Map FilePath MapResult -> Graph FilePath
resultToGraph = fmap (S.fromList . mapMaybe onlyLocalMaps . mapresultDepends) resultToGraph = mapWithKey (\p r -> S.fromList
where onlyLocalMaps = \case . mapMaybe (onlyLocalMaps (takeDirectory p))
LocalMap path -> Just (normalise "" path) . mapresultDepends $ r)
where onlyLocalMaps prefix = \case
LocalMap path -> Just (FP.normalise (prefix </> normalise "" path))
_ -> Nothing _ -> Nothing
-- | invert edges of a directed graph -- | invert edges of a directed graph
...@@ -54,12 +59,31 @@ unreachableFrom :: Ord a => a -> Graph a -> Set a ...@@ -54,12 +59,31 @@ unreachableFrom :: Ord a => a -> Graph a -> Set a
unreachableFrom entrypoint graph = unreachableFrom entrypoint graph =
nodes graph \\ reachableFrom entrypoint graph nodes graph \\ reachableFrom entrypoint graph
takeSubGraph :: (Eq a, Ord a) => Int -> a -> Graph a -> Graph a
takeSubGraph i start graph
| i <= 0 = mempty
| i == 1 =
M.singleton start reachable
`M.union` M.fromList ((,mempty) <$> S.toList reachable)
| otherwise =
M.singleton start reachable
`M.union` (M.unionsWith S.union
. S.map (flip (takeSubGraph (i-1)) graph)
$ reachable)
where reachable = fromMaybe mempty (M.lookup start graph)
graphToDot :: Graph FilePath -> Dot () graphToDot :: Graph FilePath -> Dot ()
graphToDot graph = do graphToDot graph = do
nodes <- traverseWithKey main <- D.node [("label","main.json")]
(\name edges -> D.node [("label",name)] <&> (,edges)) nodes' <- traverseMaybeWithKey
(\name edges -> if name /= "main.json"
then D.node [("label",name)] <&> (, edges) <&> Just
else pure Nothing
)
graph graph
let reachable = fromMaybe mempty (M.lookup "main.json" graph)
let nodes = M.insert "main.json" (main,reachable) nodes'
forM_ nodes $ \(node, edges) -> forM_ nodes $ \(node, edges) ->
forM_ edges $ \key -> forM_ edges $ \key ->
case M.lookup key nodes of case M.lookup key nodes of
......
...@@ -3,6 +3,7 @@ ...@@ -3,6 +3,7 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf #-}
module Main where module Main where
...@@ -18,7 +19,7 @@ import qualified Data.Text.IO as T ...@@ -18,7 +19,7 @@ import qualified Data.Text.IO as T
import System.Exit (ExitCode (..), exitWith) import System.Exit (ExitCode (..), exitWith)
import WithCli import WithCli
import CheckDir (recursiveCheckDir, resultIsFatal) import CheckDir (recursiveCheckDir, resultIsFatal, DirResult (dirresultGraph))
import Control.Monad (when) import Control.Monad (when)
import LintConfig (LintConfig (..), patchConfig) import LintConfig (LintConfig (..), patchConfig)
import System.IO (hPutStrLn, stderr) import System.IO (hPutStrLn, stderr)
...@@ -26,6 +27,7 @@ import Types (Level (..)) ...@@ -26,6 +27,7 @@ import Types (Level (..))
import Util (printPretty) import Util (printPretty)
import qualified Version as V (version) import qualified Version as V (version)
import WriteRepo (writeAdjustedRepository) import WriteRepo (writeAdjustedRepository)
import Text.Dot (showDot)
-- | the options this cli tool can take -- | the options this cli tool can take
data Options = Options data Options = Options
...@@ -46,6 +48,7 @@ data Options = Options ...@@ -46,6 +48,7 @@ data Options = Options
, config :: Maybe (LintConfig Maybe) , config :: Maybe (LintConfig Maybe)
-- ^ a "patch" for the configuration file -- ^ a "patch" for the configuration file
, version :: Bool , version :: Bool
, dot :: Bool
} deriving (Show, Generic, HasArguments) } deriving (Show, Generic, HasArguments)
...@@ -73,10 +76,12 @@ run options = do ...@@ -73,10 +76,12 @@ run options = do
lints <- recursiveCheckDir lintconfig repo entry lints <- recursiveCheckDir lintconfig repo entry
if json options if | dot options ->
then printLB putStrLn (showDot $ dirresultGraph lints)
$ if pretty options then encodePretty lints else encode lints | json options ->
else printPretty (level, lints) printLB
$ if pretty options then encodePretty lints else encode lints
| otherwise -> printPretty (level, lints)
case out options of case out options of
Nothing -> exitWith $ case resultIsFatal lintconfig lints of Nothing -> exitWith $ case resultIsFatal lintconfig lints of
......
...@@ -72,7 +72,8 @@ executable walint ...@@ -72,7 +72,8 @@ executable walint
mtl, mtl,
text, text,
template-haskell, template-haskell,
process process,
dotgen
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
other-modules: Version other-modules: Version
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment