Skip to content

Commit

Permalink
graphex graph all fails when no modules match the query (#59)
Browse files Browse the repository at this point in the history
  • Loading branch information
ramirez7 authored Apr 3, 2024
1 parent 7e7c480 commit f803f8f
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 1 deletion.
2 changes: 2 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@

## Unreleased changes

- `graphex graph all` now fails when no modules match the query.

## 0.1.2.1

- Fix `graphex cabal` for units with multiple source directories.
Expand Down
5 changes: 4 additions & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
{-# LANGUAGE ApplicativeDo #-}
module Main where

import Control.Monad (when)
import Data.Aeson (encode)
import Data.Bool (bool)
import qualified Data.ByteString.Lazy as BL
import qualified Data.Csv as CSV
import Data.Foldable
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
Expand Down Expand Up @@ -137,7 +139,8 @@ main = customExecParser (prefs showHelpOnError) opts >>= \case
AllDepsOn{..} -> do
let ms =
if | useRegex -> filter (\m -> any (m =~) patterns) (graphNodes graph)
| otherwise -> NE.toList patterns
| otherwise -> filter (flip Map.member (unGraph graph)) $ NE.toList patterns
when (null ms) $ error $ unwords ["No nodes in the graph match:", show patterns]
printStrs $ foldMap (allDepsOn graph) ms
Rankings -> printStrs $ fmap (\(n,m) -> m <> " - " <> (T.pack . show) n) $ rankings graph
FindLongest -> printStrs $ longest graph
Expand Down

0 comments on commit f803f8f

Please sign in to comment.