├── .envrc ├── .gitignore ├── README.md ├── backend ├── Setup.hs ├── app │ └── Main.hs ├── grafanix.cabal ├── src │ ├── Config.hs │ ├── Nix.hs │ ├── Parser.hs │ └── Types.hs └── test │ ├── Spec.hs │ ├── edge.dot │ ├── node.dot │ └── zlib-deps.dot ├── default.nix ├── frontend ├── default.nix ├── elm-srcs.nix ├── elm.json ├── registry.dat ├── scripts │ ├── build.sh │ └── watch.sh └── src │ ├── JS.elm │ └── Main.elm ├── grafanix.png ├── nix ├── grafanix-backend.nix ├── grafanix-release.nix ├── grafanix.nix ├── sources.json └── sources.nix ├── shell.nix ├── static ├── drawGraph.js ├── index.html ├── main.css └── nix.png └── treefmt.toml /.envrc: -------------------------------------------------------------------------------- 1 | use nix 2 | 3 | -------------------------------------------------------------------------------- /.gitignore: -------------------------------------------------------------------------------- 1 | # cabal (old an new build dirs) 2 | backend/dist 3 | backend/dist-newstyle 4 | backend/cabal.* 5 | backend/.ghc.environment.* 6 | 7 | # Elm stuff 8 | frontend/elm-stuff 9 | 10 | # Thirdparty assets 11 | static/bootstrap.css 12 | static/d3.js 13 | 14 | # Compiled Elm code 15 | static/main.js 16 | 17 | # Nix symlinks 18 | **/result 19 | **/result-* 20 | -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- 1 | # Grafanix 2 | 3 | This tool can visualize build and runtime dependencies of Nix derivations. 4 | 5 | ![](grafanix.png) 6 | 7 | ## Building 8 | 9 | ```bash 10 | nix-build --attr grafanix --out-link grafanix 11 | ``` 12 | 13 | If you don't want to wait, grab the latest [release](https://github.com/stolyaroleh/grafanix/releases). 14 | 15 | ## Running 16 | 17 | ```bash 18 | ./grafanix/bin/grafanix --help # show available options 19 | ./grafanix/bin/grafanix # start Grafanix, use 20 | ``` 21 | 22 | After starting Grafanix, open `localhost:3000` in your browser. 23 | 24 | ## Hacking 25 | 26 | I suggest using VSCode with the following plugins: 27 | 28 | - ghcide 29 | - HTML CSS Support 30 | - Elm Support 31 | 32 | Make sure you run it in a shell with all necessary tooling: 33 | 34 | ```bash 35 | nix-shell --command "code" 36 | ``` 37 | 38 | ### Backend 39 | 40 | ```bash 41 | cd backend 42 | 43 | cabal new-build # Build it 44 | cabal new-repl # Start a REPL 45 | cabal new-run grafanix --static-path="../static" # Run it, serve static assets from project directory 46 | ``` 47 | 48 | ### Frontend 49 | 50 | ```bash 51 | cd frontend 52 | 53 | ./scripts/watch.sh # Rebuild on every change 54 | ``` 55 | 56 | ### Formatting 57 | 58 | ```bash 59 | treefmt 60 | ``` -------------------------------------------------------------------------------- /backend/Setup.hs: -------------------------------------------------------------------------------- 1 | import Distribution.Simple 2 | main = defaultMain 3 | -------------------------------------------------------------------------------- /backend/app/Main.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Control.Error (Script) 4 | import System.Environment (getExecutablePath) 5 | import System.FilePath ((), takeDirectory) 6 | import Protolude hiding (get) 7 | import Web.Scotty 8 | import Network.Wai.Middleware.Cors (simpleCors) 9 | import Network.Wai.Middleware.Static (addBase, staticPolicy) 10 | import Config 11 | import qualified Nix 12 | import Types (depsToJson, makeEnv, runApp) 13 | 14 | safeIO :: Script a -> ActionM a 15 | safeIO script = do 16 | result <- liftIO $ runExceptT script 17 | case result of 18 | Right a -> return a 19 | Left err -> do 20 | putText err 21 | raise . toS $ err 22 | 23 | findStaticAssets :: StaticAssetLocation -> IO Text 24 | findStaticAssets (Path p) = return p 25 | findStaticAssets InstallLocation = do 26 | exePath <- getExecutablePath 27 | let installLocation = takeDirectory . takeDirectory $ exePath 28 | return $ toS (installLocation "static") 29 | 30 | runGrafanix :: Config -> IO () 31 | runGrafanix config = do 32 | env <- makeEnv config 33 | staticAssets <- toS <$> findStaticAssets (staticPath config) 34 | putStrLn $ "Serving static assets from " <> staticAssets 35 | scotty (port config) 36 | $ do 37 | middleware simpleCors 38 | middleware $ staticPolicy (addBase staticAssets) 39 | get "/" $ file (staticAssets <> "/index.html") 40 | get "/deps/:packageName/" 41 | $ do 42 | pkgName <- param "packageName" 43 | pkgPath <- safeIO $ runApp env $ Nix.pkgPath pkgName 44 | (graph, infoMap, whyMap) 45 | <- safeIO $ runApp env $ Nix.depGraph pkgPath 46 | json $ depsToJson graph infoMap whyMap 47 | get "/build-deps/:packageName" 48 | $ do 49 | pkgName <- param "packageName" 50 | pkgPath <- safeIO $ runApp env $ Nix.drvPath pkgName 51 | (graph, infoMap, whyMap) 52 | <- safeIO $ runApp env $ Nix.depGraph pkgPath 53 | json $ depsToJson graph infoMap whyMap 54 | 55 | main :: IO () 56 | main = runGrafanix =<< readConfig 57 | -------------------------------------------------------------------------------- /backend/grafanix.cabal: -------------------------------------------------------------------------------- 1 | name: grafanix-backend 2 | version: 0.1.0.0 3 | author: Oleh Stolyar 4 | maintainer: stolyar.oleh@gmail.com 5 | license: MIT 6 | copyright: 2018 Oleh Stolyar 7 | category: Web 8 | build-type: Simple 9 | cabal-version: >=1.10 10 | 11 | library grafanix-internal 12 | hs-source-dirs: src 13 | exposed-modules: Config 14 | , Nix 15 | , Parser 16 | , Types 17 | 18 | build-depends: base 19 | , aeson 20 | , attoparsec 21 | , bytestring 22 | , containers 23 | , errors 24 | , hashable 25 | , lrucache 26 | , optparse-applicative 27 | , protolude 28 | , text 29 | , typed-process 30 | , vector 31 | 32 | default-language: Haskell2010 33 | default-extensions: DuplicateRecordFields 34 | , DeriveGeneric 35 | , FlexibleContexts 36 | , GeneralizedNewtypeDeriving 37 | , NoImplicitPrelude 38 | , MultiParamTypeClasses 39 | , OverloadedStrings 40 | , RecordWildCards 41 | , ScopedTypeVariables 42 | , StandaloneDeriving 43 | , TupleSections 44 | , TypeApplications 45 | 46 | ghc-options: -Wall 47 | 48 | executable grafanix 49 | hs-source-dirs: app 50 | main-is: Main.hs 51 | 52 | build-depends: base 53 | , filepath 54 | , grafanix-internal 55 | , errors 56 | , protolude 57 | , scotty 58 | , wai-cors 59 | , wai-middleware-static 60 | 61 | default-language: Haskell2010 62 | default-extensions: NoImplicitPrelude 63 | , OverloadedStrings 64 | ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N 65 | 66 | test-suite test 67 | type: exitcode-stdio-1.0 68 | hs-source-dirs: test 69 | main-is: Spec.hs 70 | 71 | build-depends: base 72 | , grafanix-internal 73 | , text 74 | , hspec 75 | , hspec-attoparsec 76 | 77 | default-language: Haskell2010 78 | default-extensions: OverloadedStrings -------------------------------------------------------------------------------- /backend/src/Config.hs: -------------------------------------------------------------------------------- 1 | module Config (Config(..), StaticAssetLocation(..), devConfig, readConfig) where 2 | 3 | import Data.String (fromString) 4 | import Options.Applicative 5 | import Protolude hiding (option) 6 | 7 | data StaticAssetLocation = InstallLocation 8 | | Path Text 9 | deriving (Show) 10 | 11 | instance IsString StaticAssetLocation where 12 | fromString = Path . toS 13 | 14 | data Config = Config { nixpkgsPath :: Text 15 | , staticPath :: StaticAssetLocation 16 | , duCacheSize :: Integer 17 | , whyCacheSize :: Integer 18 | , port :: Int 19 | } 20 | deriving (Show) 21 | 22 | devConfig :: Config 23 | devConfig = Config { nixpkgsPath = "" 24 | , staticPath = Path "../static" 25 | , duCacheSize = 4096 26 | , whyCacheSize = 2048 27 | , port = 3000 28 | } 29 | 30 | config :: Parser Config 31 | config = Config 32 | <$> strOption 33 | (long "pkgs-path" 34 | <> help "Package set path" 35 | <> showDefault 36 | <> value (nixpkgsPath devConfig)) 37 | <*> option 38 | str 39 | (long "static-path" 40 | <> help "Path to serve static assets from" 41 | <> showDefault 42 | <> value InstallLocation) 43 | <*> pure (duCacheSize devConfig) 44 | <*> pure (whyCacheSize devConfig) 45 | <*> option 46 | auto 47 | (long "port" 48 | <> help "Port to listen on" 49 | <> showDefault 50 | <> value (port devConfig)) 51 | 52 | readConfig :: IO Config 53 | readConfig = execParser opts 54 | where 55 | opts = info 56 | (config <**> helper) 57 | (fullDesc <> header "Grafanix - Visualize your Nix dependencies") 58 | -------------------------------------------------------------------------------- /backend/src/Nix.hs: -------------------------------------------------------------------------------- 1 | module Nix 2 | ( drvPath, 3 | pkgPath, 4 | depGraph, 5 | ) 6 | where 7 | 8 | import Config 9 | import Control.Error 10 | ( Script, 11 | scriptIO, 12 | ) 13 | import Data.Attoparsec.Text 14 | ( Parser, 15 | parseOnly, 16 | ) 17 | import qualified Data.ByteString.Lazy as L 18 | import qualified Data.ByteString.Char8 as C 19 | import Data.Cache.LRU.IO (AtomicLRU, insert, lookup) 20 | import qualified Data.Map as Map 21 | import qualified Data.Text as Text 22 | import Data.Vector (Vector) 23 | import qualified Data.Vector as Vector 24 | import qualified Parser 25 | import Protolude 26 | import System.Process.Typed 27 | import Types 28 | 29 | decolor :: ByteString -> ByteString 30 | decolor = go mempty 31 | where 32 | go acc "" = acc 33 | go acc string = 34 | let esc = '\x1b' 35 | colorSequenceStart = "\x1b[" 36 | (text, colored) = C.span (/= esc) string 37 | -- Attempt to strip a color sequence 38 | rest = case C.stripPrefix colorSequenceStart colored of 39 | Just x -> 40 | -- All color sequences look like this: ESC[#(;#)m 41 | C.drop 1 . C.dropWhile (/= 'm') $ x 42 | Nothing -> 43 | -- Just skip ESC otherwise 44 | C.dropWhile (== esc) colored 45 | in go (acc <> text) rest 46 | 47 | run :: Text -> [Text] -> Script Text 48 | run cmd args = do 49 | putText cmdline 50 | let procConfig = 51 | setStdin closed $ 52 | setStdout byteStringOutput $ 53 | setStderr closed $ 54 | proc 55 | (toS cmd) 56 | (map toS args) 57 | (exitCode, out, err) <- readProcess procConfig 58 | if exitCode == ExitSuccess 59 | then return . decodeUtf8 . decolor . L.toStrict $ out 60 | else 61 | let message = "Command '" <> cmdline <> "' failed with:\n" <> (decodeUtf8 . L.toStrict $ err) 62 | in throwError message 63 | where 64 | cmdline = cmd <> " " <> Text.unwords args 65 | 66 | cached :: 67 | (Hashable k, Ord k) => AtomicLRU k v -> (k -> Script v) -> k -> Script v 68 | cached cache script k = do 69 | cachedValue <- scriptIO $ lookup k cache 70 | case cachedValue of 71 | Just v -> return v 72 | Nothing -> do 73 | v <- script k 74 | scriptIO $ insert k v cache 75 | return v 76 | 77 | parse :: Parser a -> Text -> Script a 78 | parse parser text = case parseOnly parser text of 79 | Right a -> return a 80 | Left err -> throwError . toS $ err 81 | 82 | drvPath :: Text -> App Text 83 | drvPath pkgExpr = do 84 | nixpkgs <- asks (nixpkgsPath . config) 85 | out <- lift $ run "nix-instantiate" ["--expr", "with import " <> nixpkgs <> " {}; " <> pkgExpr] 86 | lift $ parse Parser.nixPath out 87 | 88 | pkgPath :: Text -> App Text 89 | pkgPath pkgExpr = do 90 | nixpkgs <- asks (nixpkgsPath . config) 91 | out <- lift $ run "nix-build" ["--expr", "with import " <> nixpkgs <> " {}; " <> pkgExpr, "--no-out-link"] 92 | lift $ parse Parser.nixPath out 93 | 94 | sizeAndClosureSize :: Text -> Script (Int, Int) 95 | sizeAndClosureSize path = do 96 | out <- run "nix" ["path-info", "--size", "--closure-size", path] 97 | parse Parser.sizeAndClosureSize out 98 | 99 | whyDepends :: (Text, Text) -> Script (Vector Why) 100 | whyDepends (src, dest) = do 101 | out <- run "nix" ["why-depends", "--all", src, dest] 102 | parse Parser.whyDepends out 103 | 104 | info :: Text -> App Info 105 | info path = do 106 | sizeCache <- asks sizeCache 107 | (size, closureSize) <- lift $ cached sizeCache sizeAndClosureSize path 108 | (sha, name) <- lift $ parse Parser.hashAndName path 109 | return Info {..} 110 | 111 | depGraph :: Text -> App (DepGraph, Map Int Info, Map (Int, Int) (Vector Why)) 112 | depGraph path = do 113 | out <- lift $ run "nix-store" ["--query", "--graph", path] 114 | graph <- lift $ parse Parser.depGraph out 115 | let DepGraph {..} = graph 116 | infoVector <- mapM info nodes 117 | let infoMap = vectorToMap . Vector.indexed $ infoVector 118 | let textEdge (srcIndex, destIndex) = (nodes Vector.! srcIndex, nodes Vector.! destIndex) 119 | textEdges = Vector.map textEdge edges 120 | whyVector <- mapM getWhy textEdges 121 | let whyMap = vectorToMap $ Vector.zip edges whyVector 122 | return (graph, infoMap, whyMap) 123 | where 124 | vectorToMap :: Ord a => Vector (a, b) -> Map a b 125 | vectorToMap = Map.fromList . Vector.toList 126 | 127 | getWhy :: (Text, Text) -> App (Vector Why) 128 | getWhy (src, dest) = do 129 | whyCache <- asks whyCache 130 | lift $ cached whyCache whyDepends (src, dest) 131 | -------------------------------------------------------------------------------- /backend/src/Parser.hs: -------------------------------------------------------------------------------- 1 | module Parser where 2 | 3 | import Control.Monad (fail) 4 | import Data.Attoparsec.Text 5 | import Data.Char 6 | import qualified Data.Map.Strict as Map 7 | import Data.Maybe 8 | import qualified Data.Text as Text 9 | import Data.Vector (Vector) 10 | import qualified Data.Vector as Vector 11 | import Protolude hiding 12 | ( from, 13 | hash, 14 | takeWhile, 15 | to, 16 | try, 17 | ) 18 | import Types 19 | 20 | parseEither :: Parser a -> Text -> Either Text a 21 | parseEither parser text = case parseOnly parser text of 22 | Right a -> Right a 23 | Left err -> Left $ toS err 24 | 25 | restOfLine :: Parser () 26 | restOfLine = takeTill isEndOfLine *> endOfLine 27 | 28 | legalNixHashChar :: Char -> Bool 29 | legalNixHashChar = inClass "a-zA-Z0-9" 30 | 31 | legalNixFileNameChar :: Char -> Bool 32 | legalNixFileNameChar = inClass "a-zA-Z0-9+.?=_-" 33 | 34 | hashAndName :: Parser (Text, Text) 35 | hashAndName = do 36 | _ <- "/nix/store/" <|> "" 37 | hash <- takeWhile legalNixHashChar 38 | when (Text.length hash /= 32) $ fail "failed to parse hash" 39 | _ <- char '-' 40 | name <- takeWhile legalNixFileNameChar 41 | return (hash, name) 42 | 43 | nixPath :: Parser Text 44 | nixPath = do 45 | (hash, name) <- hashAndName 46 | return $ "/nix/store/" <> hash <> "-" <> name 47 | 48 | quoted :: Parser a -> Parser a 49 | quoted p = char '"' *> p <* char '"' 50 | 51 | -- Parse the output of `nix-store --query --graph`, 52 | depGraph :: Parser DepGraph 53 | depGraph = do 54 | _ <- string "digraph G {" *> restOfLine 55 | edgesOrNodes <- many (dotEdge <|> dotNode) 56 | _ <- string "}" 57 | let (n, e) = 58 | Vector.partition (isNothing . snd) . Vector.fromList $ edgesOrNodes 59 | nodes = Vector.map fst n 60 | 61 | addOne (numSoFar, acc) name = (numSoFar + 1, Map.insert name numSoFar acc) 62 | (_, index) = Vector.foldl addOne (0, Map.empty) nodes 63 | 64 | mkEdge (source, Just target) = 65 | Just (index Map.! source, index Map.! target) 66 | mkEdge _ = Nothing 67 | edges = Vector.map fromJust . Vector.filter isJust . Vector.map mkEdge $ e 68 | return $ DepGraph {..} 69 | 70 | dotNode :: Parser (Text, Maybe Text) 71 | dotNode = do 72 | name <- quoted nixPath <* string " [" <* restOfLine 73 | return (name, Nothing) 74 | 75 | dotEdge :: Parser (Text, Maybe Text) 76 | dotEdge = do 77 | to <- quoted nixPath 78 | _ <- string " -> " 79 | from <- quoted nixPath 80 | _ <- restOfLine 81 | return (from, Just to) 82 | 83 | -- Given the output of `nix why-depends --all $from $to`, 84 | -- produce a list of reasons why `from` directly depends on `to`. 85 | -- The output of `why-depends` will print the shortest paths first, 86 | -- which is why we only need to parse the first level of indentation until 87 | -- the first "=> " 88 | whyDepends :: Parser (Vector Why) 89 | whyDepends = do 90 | _ <- nixPath *> string "\n" 91 | whys <- 92 | choice 93 | [ why `manyTill` arrow, 94 | return [] 95 | ] 96 | return $ Vector.fromList whys 97 | where 98 | -- `filepath:…reason…` => Why 99 | why :: Parser Why 100 | why = do 101 | skipWhile isIndent 102 | file <- takeTill (== ':') <* takeTill (== '…') <* char '…' 103 | reason <- takeTill (== '…') 104 | restOfLine 105 | return Why {..} 106 | 107 | isIndent :: Char -> Bool 108 | isIndent c = c == ' ' || c == '║' || c == '╠' || c == '╚' || c == '═' 109 | 110 | arrow :: Parser () 111 | arrow = do 112 | skipWhile isIndent 113 | _ <- string "=> " 114 | restOfLine 115 | 116 | -- Given the output of `nix path-info --size --closure-size $path`, 117 | -- get size and closure size 118 | sizeAndClosureSize :: Parser (Int, Int) 119 | sizeAndClosureSize = do 120 | _ <- nixPath 121 | skipSpace 122 | size <- decimal 123 | skipSpace 124 | closureSize <- decimal 125 | restOfLine 126 | return (size, closureSize) 127 | -------------------------------------------------------------------------------- /backend/src/Types.hs: -------------------------------------------------------------------------------- 1 | module Types 2 | ( App, 3 | Env (..), 4 | Info (..), 5 | Why (..), 6 | DepGraph (..), 7 | emptyGraph, 8 | depsToJson, 9 | makeEnv, 10 | runApp, 11 | ) 12 | where 13 | 14 | import Config 15 | import Control.Error (Script) 16 | import Data.Aeson 17 | ( ToJSON, 18 | Value, 19 | object, 20 | toJSON, 21 | ) 22 | import Data.Cache.LRU.IO 23 | ( AtomicLRU, 24 | newAtomicLRU, 25 | ) 26 | import qualified Data.Map as Map 27 | import Data.Maybe 28 | import Data.Vector (Vector) 29 | import qualified Data.Vector as Vector 30 | import GHC.Generics 31 | import Protolude 32 | 33 | type App = ReaderT Env Script 34 | 35 | runApp :: Env -> App a -> Script a 36 | runApp = flip runReaderT 37 | 38 | -- Global application state 39 | -- Since we are only interested in /nix/store and the store is immutable, 40 | -- it is safe to cache information about store paths. 41 | data Env = Env 42 | { config :: Config, 43 | -- Cache storing sizes and closure sizes. 44 | sizeCache :: AtomicLRU Text (Int, Int), 45 | -- Cache storing reasons why there is a dependency between two store paths (src, dest). 46 | whyCache :: AtomicLRU (Text, Text) (Vector Why) 47 | } 48 | 49 | makeEnv :: Config -> IO Env 50 | makeEnv config = do 51 | sizeCache <- newAtomicLRU (Just . duCacheSize $ config) 52 | whyCache <- newAtomicLRU (Just . whyCacheSize $ config) 53 | return Env {..} 54 | 55 | -- A node in a dependency tree 56 | data Info = Info 57 | { name :: Text, 58 | sha :: Text, 59 | size :: Int, 60 | closureSize :: Int 61 | } 62 | deriving (Eq, Show) 63 | 64 | -- A reason why a node depends on its parent 65 | data Why = Why 66 | { file :: Text, 67 | reason :: Text 68 | } 69 | deriving (Eq, Show, Generic) 70 | 71 | instance ToJSON Why 72 | 73 | data DepGraph = DepGraph 74 | { nodes :: Vector Text, 75 | edges :: Vector (Int, Int) 76 | } 77 | deriving (Show) 78 | 79 | emptyGraph :: DepGraph 80 | emptyGraph = DepGraph {nodes = Vector.empty, edges = Vector.empty} 81 | 82 | depsToJson :: DepGraph -> Map Int Info -> Map (Int, Int) (Vector Why) -> Value 83 | depsToJson graph infos whys = 84 | object 85 | [ ("nodes", toJSON . Vector.imapMaybe mkNode $ nodes graph), 86 | ("links", toJSON . Vector.mapMaybe mkLink $ edges graph) 87 | ] 88 | where 89 | mkNode :: Int -> Text -> Maybe Value 90 | mkNode n _ = do 91 | Info {..} <- infos Map.!? n 92 | return $ 93 | object 94 | [ ("name", toJSON name), 95 | ("size", toJSON size), 96 | ("sha", toJSON sha), 97 | ("closureSize", toJSON closureSize) 98 | ] 99 | mkLink :: (Int, Int) -> Maybe Value 100 | mkLink (sourceIndex, targetIndex) = do 101 | why <- whys Map.!? (sourceIndex, targetIndex) 102 | return $ 103 | object 104 | [ ("source", toJSON sourceIndex), 105 | ("target", toJSON targetIndex), 106 | ("why", toJSON why) 107 | ] 108 | -------------------------------------------------------------------------------- /backend/test/Spec.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Test.Hspec 4 | import Test.Hspec.Attoparsec 5 | 6 | import Data.Text (Text) 7 | import Data.Text.IO (readFile) 8 | import Parser 9 | import Prelude hiding (readFile) 10 | 11 | main :: IO () 12 | main = do 13 | nodeDot <- readFile "./test/node.dot" 14 | edgeDot <- readFile "./test/edge.dot" 15 | hspec $ 16 | describe "Parser" $ do 17 | describe "hashAndName" $ 18 | it "works on glibc" $ 19 | ("/nix/store/2kcrj1ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131" :: Text) ~> hashAndName 20 | `shouldParse` ("2kcrj1ksd2a14bm5sky182fv2xwfhfap", "glibc-2.26-131") 21 | describe "nixPath" $ do 22 | it "works on glibc" $ 23 | nixPath `shouldSucceedOn` 24 | ("/nix/store/2kcrj1ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131" :: Text) 25 | it "works without /nix/store" $ 26 | nixPath `shouldSucceedOn` 27 | ("2kcrj1ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131" :: Text) 28 | it "fails on illegal characters" $ 29 | nixPath `shouldFailOn` 30 | ("/nix/store/2kcrj\"ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131" :: Text) 31 | describe "quoted" $ 32 | it "can parse a nixPath in quotes" $ 33 | ("\"/nix/store/2kcrj1ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131\"" :: Text) ~> quoted nixPath 34 | `shouldParse` "/nix/store/2kcrj1ksd2a14bm5sky182fv2xwfhfap-glibc-2.26-131" 35 | describe "dotNode" $ do 36 | it "can parse a DOT node" $ 37 | dotNode `shouldSucceedOn` nodeDot 38 | it "fails on a DOT edge" $ 39 | dotNode `shouldFailOn` edgeDot 40 | describe "dotEdge" $ do 41 | it "can parse a DOT edge" $ 42 | dotEdge `shouldSucceedOn` edgeDot 43 | it "fails on a DOT node" $ 44 | dotEdge `shouldFailOn` nodeDot 45 | describe "depGraph" $ 46 | it "can parse zlib dependencies DOT" $ 47 | (depGraph `shouldSucceedOn`) =<< readFile "./test/zlib-deps.dot" 48 | -------------------------------------------------------------------------------- /backend/test/edge.dot: -------------------------------------------------------------------------------- 1 | "/nix/store/a0d6q18gxggcvb5x24nrdg6nvhbnipnb-glibc-2.27" -> "/nix/store/3lpg9gcwllklvcncc31v5lpqma7ymx5g-zlib-1.2.11" [color = "black"]; 2 | -------------------------------------------------------------------------------- /backend/test/node.dot: -------------------------------------------------------------------------------- 1 | "/nix/store/3lpg9gcwllklvcncc31v5lpqma7ymx5g-zlib-1.2.11" [label = "zlib-1.2.11", shape = box, style = filled, fillcolor = "#ff0000"]; 2 | -------------------------------------------------------------------------------- /backend/test/zlib-deps.dot: -------------------------------------------------------------------------------- 1 | digraph G { 2 | "/nix/store/3lpg9gcwllklvcncc31v5lpqma7ymx5g-zlib-1.2.11" [label = "zlib-1.2.11", shape = box, style = filled, fillcolor = "#ff0000"]; 3 | "/nix/store/a0d6q18gxggcvb5x24nrdg6nvhbnipnb-glibc-2.27" -> "/nix/store/3lpg9gcwllklvcncc31v5lpqma7ymx5g-zlib-1.2.11" [color = "black"]; 4 | "/nix/store/a0d6q18gxggcvb5x24nrdg6nvhbnipnb-glibc-2.27" [label = "glibc-2.27", shape = box, style = filled, fillcolor = "#ff0000"]; 5 | } -------------------------------------------------------------------------------- /default.nix: -------------------------------------------------------------------------------- 1 | {}: 2 | let 3 | sources = import ./nix/sources.nix; 4 | pkgs = import sources.nixpkgs { }; 5 | 6 | haskellCompiler = "ghc927"; 7 | haskellPackages = pkgs.haskell.packages.${haskellCompiler}; 8 | 9 | static = import (sources.static-haskell-nix + "/survey") { 10 | 11 | compiler = haskellCompiler; 12 | integer-simple = false; 13 | }; 14 | staticHaskellPackages = static.haskellPackagesWithLibsReadyForStaticLinking; 15 | 16 | d3 = builtins.fetchurl { 17 | url = "https://d3js.org/d3.v5.min.js"; 18 | sha256 = "0g5529s28dm27sqp5zzff1ipva1fyipdswl51c7h3ps7715r5gjx"; 19 | }; 20 | 21 | bootstrap = builtins.fetchurl { 22 | url = "https://stackpath.bootstrapcdn.com/bootstrap/4.3.1/css/bootstrap.min.css"; 23 | sha256 = "0dldiln2s3z8iqc5ccjid2i5gh9527naas064bwly8x9lrfrxcb0"; 24 | }; 25 | in 26 | rec { 27 | backend = haskellPackages.callPackage ./nix/grafanix-backend.nix { 28 | static = false; 29 | }; 30 | backend-static = staticHaskellPackages.callPackage ./nix/grafanix-backend.nix { 31 | static = true; 32 | ncurses = static.pkgs.ncurses.override { 33 | enableStatic = true; 34 | }; 35 | zlib = static.pkgs.zlib; 36 | }; 37 | 38 | frontend = pkgs.callPackage ./frontend/default.nix { }; 39 | 40 | grafanix = pkgs.callPackage ./nix/grafanix.nix { 41 | inherit bootstrap d3; 42 | inherit backend frontend; 43 | }; 44 | grafanix-static = pkgs.callPackage ./nix/grafanix.nix { 45 | inherit bootstrap d3; 46 | inherit frontend; 47 | backend = backend-static; 48 | }; 49 | 50 | grafanix-release = pkgs.callPackage ./nix/grafanix-release.nix { 51 | grafanix = grafanix-static; 52 | }; 53 | 54 | shell = ( 55 | pkgs.haskell.lib.addBuildTools 56 | backend 57 | ( 58 | [ 59 | haskellPackages.cabal2nix 60 | haskellPackages.cabal-install 61 | haskellPackages.ghcide 62 | haskellPackages.ormolu 63 | pkgs.elm2nix 64 | pkgs.inotify-tools 65 | pkgs.niv 66 | pkgs.treefmt 67 | ] ++ frontend.buildInputs 68 | ) 69 | ).env.overrideAttrs ( 70 | old: { 71 | shellHook = '' 72 | ln -snfv ${bootstrap} ${builtins.toString ./.}/static/bootstrap.css 73 | ln -snfv ${d3} ${builtins.toString ./.}/static/d3.js 74 | ''; 75 | } 76 | ); 77 | } 78 | -------------------------------------------------------------------------------- /frontend/default.nix: -------------------------------------------------------------------------------- 1 | { lib 2 | , stdenvNoCC 3 | , elm2nix 4 | , elmPackages 5 | , nodePackages 6 | }: 7 | let 8 | srcs = ./elm-srcs.nix; 9 | in 10 | stdenvNoCC.mkDerivation { 11 | name = "grafanix"; 12 | 13 | src = lib.sourceByRegex ./. [ 14 | "src(.*elm)?" 15 | "elm.json" 16 | "build.sh" 17 | ]; 18 | 19 | buildInputs = [ 20 | elmPackages.elm 21 | nodePackages.uglify-js 22 | ] ++ lib.optionals lib.inNixShell [ 23 | elm2nix 24 | elmPackages.elm-format 25 | ]; 26 | 27 | buildPhase = elmPackages.fetchElmDeps { 28 | elmPackages = import srcs; 29 | elmVersion = "0.19.1"; 30 | registryDat = ./registry.dat; 31 | }; 32 | 33 | installPhase = '' 34 | mkdir -p $out 35 | ${scripts/build.sh} src/Main.elm 36 | cp elm.min.js $out/main.js 37 | ''; 38 | } 39 | -------------------------------------------------------------------------------- /frontend/elm-srcs.nix: -------------------------------------------------------------------------------- 1 | { 2 | 3 | "rundis/elm-bootstrap" = { 4 | sha256 = "0jn864353vbq6q73gmycbcncm26a9v0mkb6ba75ab611sq7pc5kb"; 5 | version = "5.1.0"; 6 | }; 7 | 8 | "elm/browser" = { 9 | sha256 = "1zlmx672glg7fdgkvh5jm47y85pv7pdfr5mkhg6x7ar6k000vyka"; 10 | version = "1.0.1"; 11 | }; 12 | 13 | "elm/core" = { 14 | sha256 = "1l0qdbczw91kzz8sx5d5zwz9x662bspy7p21dsr3f2rigxiix2as"; 15 | version = "1.0.2"; 16 | }; 17 | 18 | "elm/http" = { 19 | sha256 = "008bs76mnp48b4dw8qwjj4fyvzbxvlrl4xpa2qh1gg2kfwyw56v1"; 20 | version = "2.0.0"; 21 | }; 22 | 23 | "elm/bytes" = { 24 | sha256 = "02ywbf52akvxclpxwj9n04jydajcbsbcbsnjs53yjc5lwck3abwj"; 25 | version = "1.0.8"; 26 | }; 27 | 28 | "elm/file" = { 29 | sha256 = "1rljcb41dl97myidyjih2yliyzddkr2m7n74x7gg46rcw4jl0ny8"; 30 | version = "1.0.5"; 31 | }; 32 | 33 | "elm/json" = { 34 | sha256 = "0kjwrz195z84kwywaxhhlnpl3p251qlbm5iz6byd6jky2crmyqyh"; 35 | version = "1.1.3"; 36 | }; 37 | 38 | "elm/html" = { 39 | sha256 = "1n3gpzmpqqdsldys4ipgyl1zacn0kbpc3g4v3hdpiyfjlgh8bf3k"; 40 | version = "1.0.0"; 41 | }; 42 | 43 | "avh4/elm-color" = { 44 | sha256 = "0n16wnvp87x9az3m5qjrl6smsg7051m719xn5d244painx8xmpzq"; 45 | version = "1.0.0"; 46 | }; 47 | 48 | "elm/url" = { 49 | sha256 = "0av8x5syid40sgpl5vd7pry2rq0q4pga28b4yykn9gd9v12rs3l4"; 50 | version = "1.0.0"; 51 | }; 52 | 53 | "elm/time" = { 54 | sha256 = "0vch7i86vn0x8b850w1p69vplll1bnbkp8s383z7pinyg94cm2z1"; 55 | version = "1.0.0"; 56 | }; 57 | 58 | "elm/virtual-dom" = { 59 | sha256 = "0q1v5gi4g336bzz1lgwpn5b1639lrn63d8y6k6pimcyismp2i1yg"; 60 | version = "1.0.2"; 61 | }; 62 | } 63 | -------------------------------------------------------------------------------- /frontend/elm.json: -------------------------------------------------------------------------------- 1 | { 2 | "type": "application", 3 | "source-directories": [ 4 | "src" 5 | ], 6 | "elm-version": "0.19.1", 7 | "dependencies": { 8 | "direct": { 9 | "elm/browser": "1.0.1", 10 | "elm/core": "1.0.2", 11 | "elm/html": "1.0.0", 12 | "elm/http": "2.0.0", 13 | "rundis/elm-bootstrap": "5.1.0" 14 | }, 15 | "indirect": { 16 | "avh4/elm-color": "1.0.0", 17 | "elm/bytes": "1.0.8", 18 | "elm/file": "1.0.5", 19 | "elm/json": "1.1.3", 20 | "elm/time": "1.0.0", 21 | "elm/url": "1.0.0", 22 | "elm/virtual-dom": "1.0.2" 23 | } 24 | }, 25 | "test-dependencies": { 26 | "direct": {}, 27 | "indirect": {} 28 | } 29 | } 30 | -------------------------------------------------------------------------------- /frontend/registry.dat: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/stolyaroleh/grafanix/6bf9a6188f4ca3c53327a41c5ce40d8ff57fb9e0/frontend/registry.dat -------------------------------------------------------------------------------- /frontend/scripts/build.sh: -------------------------------------------------------------------------------- 1 | #!/bin/sh 2 | set -e 3 | 4 | js="elm.js" 5 | min="elm.min.js" 6 | 7 | elm make --optimize --output=$js $@ 8 | 9 | uglifyjs $js --compress 'pure_funcs="F2,F3,F4,F5,F6,F7,F8,F9,A2,A3,A4,A5,A6,A7,A8,A9",pure_getters,keep_fargs=false,unsafe_comps,unsafe' | uglifyjs --mangle --output $min 10 | 11 | echo "Compiled size: $(cat $js | wc -c) bytes ($js)" 12 | echo "Minified size: $(cat $min | wc -c) bytes ($min)" 13 | echo "Gzipped size: $(cat $min | gzip -c | wc -c) bytes" 14 | -------------------------------------------------------------------------------- /frontend/scripts/watch.sh: -------------------------------------------------------------------------------- 1 | #!/bin/sh 2 | 3 | watch() { 4 | inotifywait --recursive ./src --include ".*\.elm" \ 5 | --event modify 6 | elm make ./src/Main.elm --output ../static/main.js 7 | } 8 | 9 | while true 10 | do 11 | watch 12 | done 13 | -------------------------------------------------------------------------------- /frontend/src/JS.elm: -------------------------------------------------------------------------------- 1 | port module JS exposing (drawGraph, sessionRestore, sessionSave) 2 | 3 | 4 | port drawGraph : String -> Cmd msg 5 | 6 | 7 | port sessionSave : String -> Cmd msg 8 | 9 | 10 | port sessionRestore : (String -> msg) -> Sub msg 11 | -------------------------------------------------------------------------------- /frontend/src/Main.elm: -------------------------------------------------------------------------------- 1 | module Main exposing (main) 2 | 3 | import Bootstrap.Button as Button 4 | import Bootstrap.ButtonGroup as ButtonGroup 5 | import Bootstrap.Form as Form 6 | import Bootstrap.Form.Fieldset as Fieldset 7 | import Bootstrap.Form.Input as Input 8 | import Bootstrap.Form.InputGroup as InputGroup 9 | import Bootstrap.Utilities.Flex as Flex 10 | import Bootstrap.Utilities.Size as Size 11 | import Bootstrap.Utilities.Spacing as Spacing 12 | import Browser 13 | import Html exposing (Html, div, h5, text) 14 | import Html.Attributes exposing (id, style, value) 15 | import Html.Events exposing (onClick, onInput, onSubmit) 16 | import Http 17 | import JS exposing (drawGraph, sessionRestore, sessionSave) 18 | 19 | 20 | type alias Expr = 21 | String 22 | 23 | 24 | type alias GraphData = 25 | String 26 | 27 | 28 | type ClosureType 29 | = Build 30 | | Runtime 31 | 32 | 33 | type alias Model = 34 | { expr : String 35 | , closureType : ClosureType 36 | , tracker : Maybe String 37 | } 38 | 39 | 40 | init : () -> ( Model, Cmd Msg ) 41 | init _ = 42 | ( { expr = "" 43 | , closureType = Runtime 44 | , tracker = Nothing 45 | } 46 | , Cmd.none 47 | ) 48 | 49 | 50 | type Msg 51 | = SetExpr Expr 52 | | SetClosureType ClosureType 53 | | DrawGraph (Result Http.Error GraphData) 54 | | RestoreSession String 55 | | Submit 56 | 57 | 58 | update : Msg -> Model -> ( Model, Cmd Msg ) 59 | update msg model = 60 | let 61 | noop = 62 | ( model, Cmd.none ) 63 | in 64 | case msg of 65 | SetExpr newExpr -> 66 | ( { model | expr = newExpr }, Cmd.none ) 67 | 68 | SetClosureType newClosureType -> 69 | if model.closureType == newClosureType then 70 | noop 71 | 72 | else 73 | update Submit { model | closureType = newClosureType } 74 | 75 | DrawGraph data -> 76 | case data of 77 | Ok graphData -> 78 | ( model, drawGraph graphData ) 79 | 80 | Err err -> 81 | noop 82 | 83 | RestoreSession newExpr -> 84 | let 85 | newModel = 86 | { model | expr = newExpr } 87 | in 88 | update Submit newModel 89 | 90 | Submit -> 91 | let 92 | saveState = 93 | sessionSave model.expr 94 | in 95 | ( model, Cmd.batch [ saveState, fetchGraph model ] ) 96 | 97 | 98 | fetchGraph : Model -> Cmd Msg 99 | fetchGraph model = 100 | let 101 | method = 102 | case model.closureType of 103 | Runtime -> 104 | "/deps/" 105 | 106 | Build -> 107 | "/build-deps/" 108 | 109 | url = 110 | method ++ model.expr 111 | 112 | maybeCancel tracker = 113 | case tracker of 114 | Just s -> 115 | [ Http.cancel s ] 116 | 117 | Nothing -> 118 | [] 119 | in 120 | if Just model.expr == model.tracker then 121 | Cmd.none 122 | 123 | else 124 | Cmd.batch 125 | (maybeCancel model.tracker 126 | ++ [ Http.request 127 | { method = "GET" 128 | , timeout = Nothing 129 | , tracker = Just url 130 | , body = Http.emptyBody 131 | , headers = [] 132 | , url = url 133 | , expect = Http.expectString DrawGraph 134 | } 135 | ] 136 | ) 137 | 138 | 139 | subscriptions : Model -> Sub Msg 140 | subscriptions model = 141 | sessionRestore RestoreSession 142 | 143 | 144 | view : Model -> Browser.Document Msg 145 | view model = 146 | let 147 | packageInputGroup = 148 | InputGroup.config 149 | (InputGroup.text 150 | [ Input.placeholder "Package or expression" 151 | , Input.onInput SetExpr 152 | , Input.attrs [ value model.expr ] 153 | ] 154 | ) 155 | |> InputGroup.attrs [ Size.w100 ] 156 | |> InputGroup.successors 157 | [ InputGroup.button [ Button.primary ] [ text "Go!" ] ] 158 | |> InputGroup.view 159 | 160 | packageInput = 161 | Form.form 162 | [ onSubmit Submit 163 | , Spacing.pb2 164 | , Spacing.pt2 165 | , Spacing.pl3 166 | , Spacing.pr3 167 | , Size.w100 168 | , style "position" "absolute" 169 | , style "top" "0px" 170 | ] 171 | [ packageInputGroup ] 172 | 173 | closureButtonGroup = 174 | ButtonGroup.radioButtonGroup 175 | [ ButtonGroup.attrs [ Size.w100 ] ] 176 | [ ButtonGroup.radioButton 177 | (model.closureType == Runtime) 178 | [ Button.primary, Button.onClick <| SetClosureType Runtime ] 179 | [ text "Runtime" ] 180 | , ButtonGroup.radioButton 181 | (model.closureType == Build) 182 | [ Button.primary, Button.onClick <| SetClosureType Build ] 183 | [ text "Build" ] 184 | ] 185 | 186 | closureButtons = 187 | Fieldset.config 188 | |> Fieldset.attrs 189 | [ Spacing.pb2 190 | , Spacing.pt2 191 | , Spacing.pl3 192 | , Spacing.pr3 193 | , style "position" "absolute" 194 | , style "bottom" "0px" 195 | ] 196 | |> Fieldset.children 197 | [ h5 [] [ text "Closure" ] 198 | , closureButtonGroup 199 | ] 200 | |> Fieldset.view 201 | in 202 | { title = "Grafanix" 203 | , body = 204 | [ div 205 | [ style "display" "flex" 206 | , Size.h100 207 | , Flex.col 208 | ] 209 | [ packageInput 210 | , div [ id "vis" ] [] 211 | , closureButtons 212 | ] 213 | ] 214 | } 215 | 216 | 217 | main = 218 | Browser.document 219 | { init = init 220 | , update = update 221 | , view = view 222 | , subscriptions = subscriptions 223 | } 224 | -------------------------------------------------------------------------------- /grafanix.png: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/stolyaroleh/grafanix/6bf9a6188f4ca3c53327a41c5ce40d8ff57fb9e0/grafanix.png -------------------------------------------------------------------------------- /nix/grafanix-backend.nix: -------------------------------------------------------------------------------- 1 | { mkDerivation 2 | , lib 3 | 4 | , aeson 5 | , attoparsec 6 | , base 7 | , bytestring 8 | , containers 9 | , errors 10 | , filepath 11 | , hashable 12 | , hspec 13 | , hspec-attoparsec 14 | , lrucache 15 | , optparse-applicative 16 | , protolude 17 | , scotty 18 | , text 19 | , typed-process 20 | , vector 21 | , wai-cors 22 | , wai-middleware-static 23 | 24 | , static ? false 25 | , ncurses ? null 26 | , zlib ? null 27 | }: 28 | mkDerivation { 29 | pname = "grafanix-backend"; 30 | version = "0.1.0.0"; 31 | src = lib.sourceByRegex ../backend [ 32 | "app" 33 | "app/.*\.hs" 34 | "src" 35 | "src/.*\.hs" 36 | "test" 37 | "test/.*\.hs" 38 | "test/.*\.dot" 39 | "grafanix\.cabal" 40 | "Setup\.hs" 41 | ]; 42 | 43 | isExecutable = true; 44 | enableSharedLibraries = false; 45 | enableSharedExecutables = false; 46 | configureFlags = 47 | lib.optionals static [ 48 | "--ghc-option=-optl=-static" 49 | "--extra-lib-dirs=${zlib.static}/lib:${ncurses}/lib" 50 | ]; 51 | 52 | executableHaskellDepends = [ 53 | aeson 54 | attoparsec 55 | base 56 | bytestring 57 | containers 58 | errors 59 | filepath 60 | hashable 61 | lrucache 62 | optparse-applicative 63 | protolude 64 | scotty 65 | text 66 | typed-process 67 | vector 68 | wai-cors 69 | wai-middleware-static 70 | ]; 71 | testHaskellDepends = [ base hspec hspec-attoparsec ]; 72 | license = lib.licenses.mit; 73 | } 74 | -------------------------------------------------------------------------------- /nix/grafanix-release.nix: -------------------------------------------------------------------------------- 1 | { runCommand 2 | , grafanix 3 | , zip 4 | }: 5 | let 6 | version = grafanix.version; 7 | in 8 | runCommand "grafanix-${version}.zip" { } '' 9 | cd ${grafanix} 10 | ${zip}/bin/zip -9 -r $out * 11 | '' 12 | -------------------------------------------------------------------------------- /nix/grafanix.nix: -------------------------------------------------------------------------------- 1 | { lib 2 | , d3 3 | , bootstrap 4 | , backend 5 | , frontend 6 | , stdenvNoCC 7 | }: 8 | stdenvNoCC.mkDerivation { 9 | name = "grafanix"; 10 | version = "0.3"; 11 | 12 | src = lib.sourceByRegex ../static [ 13 | "drawGraph.js" 14 | "index.html" 15 | "main.css" 16 | "nix.png" 17 | ]; 18 | 19 | phases = [ 20 | "unpackPhase" 21 | "installPhase" 22 | ]; 23 | 24 | installPhase = '' 25 | mkdir -p $out/static 26 | cp ${d3} $out/static/d3.js 27 | cp ${bootstrap} $out/static/bootstrap.css 28 | cp * $out/static 29 | cp ${frontend}/main.js $out/static 30 | 31 | mkdir -p $out/bin 32 | cp ${backend}/bin/grafanix $out/bin/grafanix 33 | ''; 34 | } 35 | -------------------------------------------------------------------------------- /nix/sources.json: -------------------------------------------------------------------------------- 1 | { 2 | "niv": { 3 | "branch": "master", 4 | "description": "Easy dependency management for Nix projects", 5 | "homepage": "https://github.com/nmattia/niv", 6 | "owner": "nmattia", 7 | "repo": "niv", 8 | "rev": "914aba08a26cb10538b84d00d6cfb01c9776d80c", 9 | "sha256": "0gx316gc7prjay5b0cr13x4zc2pdbiwxkfkpjvrlb2rml80lm4pm", 10 | "type": "tarball", 11 | "url": "https://github.com/nmattia/niv/archive/914aba08a26cb10538b84d00d6cfb01c9776d80c.tar.gz", 12 | "url_template": "https://github.com///archive/.tar.gz" 13 | }, 14 | "nixpkgs": { 15 | "branch": "23.05", 16 | "description": "Nixpkgs/NixOS branches that track the Nixpkgs/NixOS channels", 17 | "homepage": "https://github.com/NixOS/nixpkgs", 18 | "owner": "NixOS", 19 | "repo": "nixpkgs", 20 | "rev": "4ecab3273592f27479a583fb6d975d4aba3486fe", 21 | "sha256": "10wn0l08j9lgqcw8177nh2ljrnxdrpri7bp0g7nvrsn9rkawvlbf", 22 | "type": "tarball", 23 | "url": "https://github.com/NixOS/nixpkgs/archive/4ecab3273592f27479a583fb6d975d4aba3486fe.tar.gz", 24 | "url_template": "https://github.com///archive/.tar.gz" 25 | }, 26 | "static-haskell-nix": { 27 | "branch": "master", 28 | "description": "easily build most Haskell programs into fully static Linux executables", 29 | "homepage": "", 30 | "owner": "nh2", 31 | "repo": "static-haskell-nix", 32 | "rev": "88f1e2d57e3f4cd6d980eb3d8f99d5e60040ad54", 33 | "sha256": "1hf1470r9axjzjjnl9k21drvwx7wfcalpj3k578yb3qz5j1lh5nk", 34 | "type": "tarball", 35 | "url": "https://github.com/nh2/static-haskell-nix/archive/88f1e2d57e3f4cd6d980eb3d8f99d5e60040ad54.tar.gz", 36 | "url_template": "https://github.com///archive/.tar.gz" 37 | } 38 | } 39 | -------------------------------------------------------------------------------- /nix/sources.nix: -------------------------------------------------------------------------------- 1 | # This file has been generated by Niv. 2 | 3 | let 4 | 5 | # 6 | # The fetchers. fetch_ fetches specs of type . 7 | # 8 | 9 | fetch_file = pkgs: name: spec: 10 | let 11 | name' = sanitizeName name + "-src"; 12 | in 13 | if spec.builtin or true then 14 | builtins_fetchurl { inherit (spec) url sha256; name = name'; } 15 | else 16 | pkgs.fetchurl { inherit (spec) url sha256; name = name'; }; 17 | 18 | fetch_tarball = pkgs: name: spec: 19 | let 20 | name' = sanitizeName name + "-src"; 21 | in 22 | if spec.builtin or true then 23 | builtins_fetchTarball { name = name'; inherit (spec) url sha256; } 24 | else 25 | pkgs.fetchzip { name = name'; inherit (spec) url sha256; }; 26 | 27 | fetch_git = name: spec: 28 | let 29 | ref = 30 | spec.ref or ( 31 | if spec ? branch then "refs/heads/${spec.branch}" else 32 | if spec ? tag then "refs/tags/${spec.tag}" else 33 | abort "In git source '${name}': Please specify `ref`, `tag` or `branch`!" 34 | ); 35 | submodules = spec.submodules or false; 36 | submoduleArg = 37 | let 38 | nixSupportsSubmodules = builtins.compareVersions builtins.nixVersion "2.4" >= 0; 39 | emptyArgWithWarning = 40 | if submodules 41 | then 42 | builtins.trace 43 | ( 44 | "The niv input \"${name}\" uses submodules " 45 | + "but your nix's (${builtins.nixVersion}) builtins.fetchGit " 46 | + "does not support them" 47 | ) 48 | { } 49 | else { }; 50 | in 51 | if nixSupportsSubmodules 52 | then { inherit submodules; } 53 | else emptyArgWithWarning; 54 | in 55 | builtins.fetchGit 56 | ({ url = spec.repo; inherit (spec) rev; inherit ref; } // submoduleArg); 57 | 58 | fetch_local = spec: spec.path; 59 | 60 | fetch_builtin-tarball = name: throw 61 | ''[${name}] The niv type "builtin-tarball" is deprecated. You should instead use `builtin = true`. 62 | $ niv modify ${name} -a type=tarball -a builtin=true''; 63 | 64 | fetch_builtin-url = name: throw 65 | ''[${name}] The niv type "builtin-url" will soon be deprecated. You should instead use `builtin = true`. 66 | $ niv modify ${name} -a type=file -a builtin=true''; 67 | 68 | # 69 | # Various helpers 70 | # 71 | 72 | # https://github.com/NixOS/nixpkgs/pull/83241/files#diff-c6f540a4f3bfa4b0e8b6bafd4cd54e8bR695 73 | sanitizeName = name: 74 | ( 75 | concatMapStrings (s: if builtins.isList s then "-" else s) 76 | ( 77 | builtins.split "[^[:alnum:]+._?=-]+" 78 | ((x: builtins.elemAt (builtins.match "\\.*(.*)" x) 0) name) 79 | ) 80 | ); 81 | 82 | # The set of packages used when specs are fetched using non-builtins. 83 | mkPkgs = sources: system: 84 | let 85 | sourcesNixpkgs = 86 | import (builtins_fetchTarball { inherit (sources.nixpkgs) url sha256; }) { inherit system; }; 87 | hasNixpkgsPath = builtins.any (x: x.prefix == "nixpkgs") builtins.nixPath; 88 | hasThisAsNixpkgsPath = == ./.; 89 | in 90 | if builtins.hasAttr "nixpkgs" sources 91 | then sourcesNixpkgs 92 | else if hasNixpkgsPath && ! hasThisAsNixpkgsPath then 93 | import { } 94 | else 95 | abort 96 | '' 97 | Please specify either (through -I or NIX_PATH=nixpkgs=...) or 98 | add a package called "nixpkgs" to your sources.json. 99 | ''; 100 | 101 | # The actual fetching function. 102 | fetch = pkgs: name: spec: 103 | 104 | if ! builtins.hasAttr "type" spec then 105 | abort "ERROR: niv spec ${name} does not have a 'type' attribute" 106 | else if spec.type == "file" then fetch_file pkgs name spec 107 | else if spec.type == "tarball" then fetch_tarball pkgs name spec 108 | else if spec.type == "git" then fetch_git name spec 109 | else if spec.type == "local" then fetch_local spec 110 | else if spec.type == "builtin-tarball" then fetch_builtin-tarball name 111 | else if spec.type == "builtin-url" then fetch_builtin-url name 112 | else 113 | abort "ERROR: niv spec ${name} has unknown type ${builtins.toJSON spec.type}"; 114 | 115 | # If the environment variable NIV_OVERRIDE_${name} is set, then use 116 | # the path directly as opposed to the fetched source. 117 | replace = name: drv: 118 | let 119 | saneName = stringAsChars (c: if (builtins.match "[a-zA-Z0-9]" c) == null then "_" else c) name; 120 | ersatz = builtins.getEnv "NIV_OVERRIDE_${saneName}"; 121 | in 122 | if ersatz == "" then drv else 123 | # this turns the string into an actual Nix path (for both absolute and 124 | # relative paths) 125 | if builtins.substring 0 1 ersatz == "/" then /. + ersatz else /. + builtins.getEnv "PWD" + "/${ersatz}"; 126 | 127 | # Ports of functions for older nix versions 128 | 129 | # a Nix version of mapAttrs if the built-in doesn't exist 130 | mapAttrs = builtins.mapAttrs or ( 131 | f: set: with builtins; 132 | listToAttrs (map (attr: { name = attr; value = f attr set.${attr}; }) (attrNames set)) 133 | ); 134 | 135 | # https://github.com/NixOS/nixpkgs/blob/0258808f5744ca980b9a1f24fe0b1e6f0fecee9c/lib/lists.nix#L295 136 | range = first: last: if first > last then [ ] else builtins.genList (n: first + n) (last - first + 1); 137 | 138 | # https://github.com/NixOS/nixpkgs/blob/0258808f5744ca980b9a1f24fe0b1e6f0fecee9c/lib/strings.nix#L257 139 | stringToCharacters = s: map (p: builtins.substring p 1 s) (range 0 (builtins.stringLength s - 1)); 140 | 141 | # https://github.com/NixOS/nixpkgs/blob/0258808f5744ca980b9a1f24fe0b1e6f0fecee9c/lib/strings.nix#L269 142 | stringAsChars = f: s: concatStrings (map f (stringToCharacters s)); 143 | concatMapStrings = f: list: concatStrings (map f list); 144 | concatStrings = builtins.concatStringsSep ""; 145 | 146 | # https://github.com/NixOS/nixpkgs/blob/8a9f58a375c401b96da862d969f66429def1d118/lib/attrsets.nix#L331 147 | optionalAttrs = cond: as: if cond then as else { }; 148 | 149 | # fetchTarball version that is compatible between all the versions of Nix 150 | builtins_fetchTarball = { url, name ? null, sha256 }@attrs: 151 | let 152 | inherit (builtins) lessThan nixVersion fetchTarball; 153 | in 154 | if lessThan nixVersion "1.12" then 155 | fetchTarball ({ inherit url; } // (optionalAttrs (name != null) { inherit name; })) 156 | else 157 | fetchTarball attrs; 158 | 159 | # fetchurl version that is compatible between all the versions of Nix 160 | builtins_fetchurl = { url, name ? null, sha256 }@attrs: 161 | let 162 | inherit (builtins) lessThan nixVersion fetchurl; 163 | in 164 | if lessThan nixVersion "1.12" then 165 | fetchurl ({ inherit url; } // (optionalAttrs (name != null) { inherit name; })) 166 | else 167 | fetchurl attrs; 168 | 169 | # Create the final "sources" from the config 170 | mkSources = config: 171 | mapAttrs 172 | ( 173 | name: spec: 174 | if builtins.hasAttr "outPath" spec 175 | then 176 | abort 177 | "The values in sources.json should not have an 'outPath' attribute" 178 | else 179 | spec // { outPath = replace name (fetch config.pkgs name spec); } 180 | ) 181 | config.sources; 182 | 183 | # The "config" used by the fetchers 184 | mkConfig = 185 | { sourcesFile ? if builtins.pathExists ./sources.json then ./sources.json else null 186 | , sources ? if sourcesFile == null then { } else builtins.fromJSON (builtins.readFile sourcesFile) 187 | , system ? builtins.currentSystem 188 | , pkgs ? mkPkgs sources system 189 | }: rec { 190 | # The sources, i.e. the attribute set of spec name to spec 191 | inherit sources; 192 | 193 | # The "pkgs" (evaluated nixpkgs) to use for e.g. non-builtin fetchers 194 | inherit pkgs; 195 | }; 196 | 197 | in 198 | mkSources (mkConfig { }) // { __functor = _: settings: mkSources (mkConfig settings); } 199 | -------------------------------------------------------------------------------- /shell.nix: -------------------------------------------------------------------------------- 1 | (import ./default.nix { }).shell 2 | -------------------------------------------------------------------------------- /static/drawGraph.js: -------------------------------------------------------------------------------- 1 | function prettySize(bytes) { 2 | if (bytes == 0) { 3 | return '0 B'; 4 | } 5 | var i = Math.floor(Math.log(bytes) / Math.log(1024)); 6 | return (bytes / Math.pow(1024, i)).toFixed(2) * 1 + ' ' + ['B', 'kB', 'MB', 'GB', 'TB'][i]; 7 | } 8 | 9 | function prettyWhy(why) { 10 | return ( 11 | `${why.file} contains:\n` + 12 | `"${why.reason}"` 13 | ); 14 | } 15 | 16 | function truncate(str) { 17 | if (str.length < maxLabelChars) { 18 | return str; 19 | } 20 | return str.substr(0, maxLabelChars - 3) + '...'; 21 | } 22 | 23 | function nodeTitle(d) { 24 | return ( 25 | `${d.name} (${prettySize(d.size)})\n` + 26 | `closure: ${prettySize(d.closureSize)}\n` 27 | ); 28 | } 29 | 30 | function linkTitle(d) { 31 | return ( 32 | `${d.source.name} depends on ${d.target.name}\n\n` + 33 | `${d.why.map(prettyWhy).join('\n')}` 34 | ); 35 | } 36 | 37 | function connectedness(edges) { 38 | var numIncoming = {}; 39 | var numOutgoing = {}; 40 | edges.forEach(e => { 41 | numIncoming[e.target] = (numIncoming[e.target] || 0) + 1; 42 | numOutgoing[e.source] = (numOutgoing[e.source] || 0) + 1; 43 | }); 44 | return [numIncoming, numOutgoing]; 45 | } 46 | 47 | function drawGraph(data) { 48 | // Nuke previous contents 49 | var vis = d3.select("#vis"); 50 | vis.selectAll("*").remove(); 51 | 52 | if (data === null) { 53 | return; 54 | } 55 | 56 | try { 57 | draw(JSON.parse(data)); 58 | } catch (err) { 59 | console.log(err) 60 | } 61 | 62 | function draw(data) { 63 | const width = 1000; 64 | const height = 1000; 65 | const svg = vis.append('svg') 66 | .attr('viewBox', `${-width / 2} ${-height / 2} ${width} ${height}`); 67 | 68 | const zoomRect = svg 69 | .append('rect') 70 | .attr("fill", "none") 71 | .attr("pointer-events", "all") 72 | .attr('x', -5000) 73 | .attr('y', -5000) 74 | .attr('width', 10000) 75 | .attr('height', 10000) 76 | .call( 77 | d3.zoom() 78 | .on('zoom', zoomed) 79 | ); 80 | 81 | const visParent = svg.append('g'); 82 | 83 | [incoming, outgoing] = connectedness(data.links); 84 | const totalSize = data.nodes.reduce((total, n) => total + n.size, 0); 85 | const radius = d3.scaleSqrt().domain([0, totalSize]).range([10, 50]); 86 | const linkDistance = d3.scaleSqrt().clamp(true).domain([2, 10]).range([70, 200]); 87 | const collideRadius = d3.scaleSqrt().clamp(true).domain([2, 10]).range([20, 70]); 88 | 89 | const color = d3 90 | .scaleOrdinal() 91 | .range(d3.quantize(d3.interpolateRainbow, data.nodes.length + 1)); 92 | 93 | const simulation = d3.forceSimulation(data.nodes) 94 | .force( 95 | 'charge', 96 | d3.forceManyBody() 97 | .strength(-30) 98 | ) 99 | .force( 100 | 'link', 101 | d3.forceLink() 102 | .distance(link => { 103 | numOutgoing = outgoing[link.source.index]; 104 | numIncoming = incoming[link.target.index]; 105 | return linkDistance(numOutgoing + numIncoming); 106 | }) 107 | .links(data.links) 108 | ) 109 | .force( 110 | 'collide', 111 | d3.forceCollide() 112 | .radius(d => { 113 | isRoot = d.sha == data.nodes[0].sha; 114 | numIncoming = incoming[d.index]; 115 | numOutgoing = outgoing[d.index]; 116 | return collideRadius(numIncoming + numOutgoing); 117 | }) 118 | ) 119 | .on('tick', ticked); 120 | 121 | const link = visParent.selectAll('.link').data(data.links); 122 | const line = link.enter() 123 | .append('line') 124 | .attr('class', 'link') 125 | .attr('stroke', d => color(d.source.name)); 126 | 127 | const node = visParent.selectAll('.node').data(data.nodes); 128 | 129 | const g = node.enter() 130 | .append('g') 131 | .attr('class', 'node') 132 | .call( 133 | d3.drag() 134 | .on("start", dragstarted) 135 | .on("drag", dragged) 136 | .on("end", dragended) 137 | ); 138 | 139 | const rect = g 140 | .append('rect') 141 | .attr('class', 'node_label_bg') 142 | .attr('fill', d => color(d.name)) 143 | .attr('x', d => -0.2 * d.name.length * radius(d.size)) 144 | .attr('y', d => -0.5 * radius(d.size)) 145 | .attr('width', d => d.name.length * 0.4 * radius(d.size)) 146 | .attr('height', d => radius(d.size)) 147 | .on("click", clicked); 148 | 149 | // Text that appears on hover 150 | line 151 | .append('title') 152 | .style('white-space', 'nowrap') 153 | .text(linkTitle); 154 | rect 155 | .append('title') 156 | .style('white-space', 'nowrap') 157 | .text(nodeTitle); 158 | 159 | const label = g 160 | .append('text') 161 | .attr('class', 'node_label') 162 | .attr('font-size', d => `${0.5 * radius(d.size)}pt`) 163 | .attr('dy', '0.35em') 164 | .attr('pointer-events', 'none') 165 | .attr('fill', 166 | d => { 167 | const lab = d3.lab(color(d.name)) 168 | return lab.l > 50 ? 'black' : 'white' 169 | } 170 | ) 171 | .text(d => d.name); 172 | 173 | node.exit().remove() 174 | 175 | function ticked() { 176 | line.merge(link) 177 | .attr('x1', d => d.source.x) 178 | .attr('y1', d => d.source.y) 179 | .attr('x2', d => d.target.x) 180 | .attr('y2', d => d.target.y); 181 | g.merge(node) 182 | .attr( 183 | 'transform', 184 | d => `translate(${d.x}, ${d.y})` 185 | ); 186 | } 187 | 188 | function dragstarted(d) { 189 | if (!d3.event.active) simulation.alphaTarget(0.3).restart(); 190 | d.fx = d.x; 191 | d.fy = d.y; 192 | } 193 | 194 | function dragged(d) { 195 | d.fx = d3.event.x; 196 | d.fy = d3.event.y; 197 | } 198 | 199 | function dragended(d) { 200 | if (!d3.event.active) simulation.alphaTarget(0); 201 | } 202 | 203 | function clicked(d) { 204 | if (d.fx == null) { 205 | d.fx = d.x; 206 | d.fy = d.y; 207 | } else { 208 | d.fx = null; 209 | d.fy = null; 210 | } 211 | } 212 | 213 | function zoomed() { 214 | visParent.attr( 215 | 'transform', 216 | d3.event.transform 217 | ); 218 | } 219 | } 220 | } 221 | -------------------------------------------------------------------------------- /static/index.html: -------------------------------------------------------------------------------- 1 | 2 | 3 | 4 | 5 | Grafanix 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 33 | 34 | 35 | -------------------------------------------------------------------------------- /static/main.css: -------------------------------------------------------------------------------- 1 | html { 2 | height: 100%; 3 | } 4 | 5 | body { 6 | height: 100%; 7 | font-size: 16px; 8 | } 9 | 10 | .parent { 11 | display: flex; 12 | flex-direction: column; 13 | height: 100vh; 14 | } 15 | 16 | .header { 17 | background-color: #FAFAFA; 18 | border-bottom: 1px solid rgba(136, 136, 136, 0.2); 19 | padding-top: 20px; 20 | padding-bottom: 20px; 21 | } 22 | 23 | .controls { 24 | display: flex; 25 | align-items: center; 26 | justify-content: center; 27 | } 28 | 29 | .controls .name { 30 | margin-right: 10px; 31 | } 32 | 33 | .controls input { 34 | height: 20px; 35 | outline: none; 36 | } 37 | 38 | .controls input[type="text"] { 39 | border-color: rgba(136, 136, 136, 0.2); 40 | border-width: 1px; 41 | padding: 3px; 42 | margin: 0; 43 | } 44 | 45 | .controls input[type="radio"] { 46 | padding: 0; 47 | margin: 8px; 48 | } 49 | 50 | .controls #submit { 51 | height: 28px; 52 | background-color: #999999; 53 | color: white; 54 | border-color: rgba(136, 136, 136, 0.2); 55 | border-width: 1px 1px 1px 0; 56 | border-style: solid; 57 | padding: 0 8px; 58 | outline: none; 59 | } 60 | 61 | .controls #submit:hover, .controls #submit:active { 62 | background-color: #777777; 63 | cursor: pointer; 64 | } 65 | 66 | .group { 67 | padding-left: 20px; 68 | padding-right: 20px; 69 | } 70 | 71 | #vis { 72 | display: flex; 73 | flex: 1 1 auto; 74 | font: 10px sans-serif; 75 | } 76 | 77 | svg { 78 | display: flex; 79 | flex: 1 1 auto; 80 | } 81 | 82 | .link { 83 | stroke-width: 3px; 84 | stroke-opacity: 0.4; 85 | } 86 | 87 | .node_label_bg { 88 | fill-opacity: 0.9; 89 | } 90 | 91 | .node_label { 92 | text-anchor: middle; 93 | } 94 | -------------------------------------------------------------------------------- /static/nix.png: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/stolyaroleh/grafanix/6bf9a6188f4ca3c53327a41c5ce40d8ff57fb9e0/static/nix.png -------------------------------------------------------------------------------- /treefmt.toml: -------------------------------------------------------------------------------- 1 | [formatter.elm] 2 | command = "elm-format" 3 | options = ["--yes"] 4 | includes = ["*.elm"] 5 | 6 | [formatter.haskell] 7 | command = "ormolu" 8 | includes = ["*.hs"] 9 | 10 | [formatter.nix] 11 | command = "nixpkgs-fmt" 12 | includes = ["*.nix"] 13 | --------------------------------------------------------------------------------