aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs94
1 files changed, 41 insertions, 53 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 50ac0fd..ed059e5 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -50,22 +50,21 @@ module Main where
import Control.Exception (Exception, catch, throw)
import Data.Aeson qualified as A
-import Data.ByteString.Lazy (ByteString)
-import Data.ByteString.Lazy qualified as LB
import Data.ByteString.Lazy.Char8 qualified as LB8
-import Data.List as L
+import Data.Maybe (catMaybes)
import Data.Maybe qualified as Maybe
-import Data.Ord as O
import Data.String qualified as String
-import GHC.Generics (Generic)
+import Data.Text.IO qualified as T
+import Issue (Issue (..))
+import Issue qualified as I
import Options.Applicative ((<**>))
import Options.Applicative qualified as O
import System.Exit (ExitCode (ExitFailure), exitWith)
import System.FilePath as F
import System.IO (hPutStrLn, stderr)
import System.Process.Typed qualified as P
-import TreeGrepper.Match (Match (..), Position (..))
-import TreeGrepper.Match qualified as TM
+import TreeGrepper.Match qualified as G
+import TreeGrepper.Result qualified as G
data Options = Options
{ optCommand :: Command
@@ -108,25 +107,24 @@ main = do
(\filename -> catch (fmap Just (getIssues filename)) (forgetGetIssuesExceptions))
files
)
- ( \(InvalidTreeGrepperResult error) ->
+ ( \(InvalidTreeGrepperResult e) ->
do
- hPutStrLn stderr error
+ hPutStrLn stderr e
exitWith (ExitFailure 1)
)
- let issuesWithMarker = issues
- issuesWithTags = issuesWithMarker
- issuesFilteredByTags = issuesWithTags
case options of
List -> mapM_ listMatches $ concat issues
Show -> mapM_ showMatches $ concat issues
-showMatches :: TreeGrepperResult -> IO ()
-showMatches treeGrepperResult =
- mapM_ (putStrLn . (.text)) $ treeGrepperResult.matches
+showMatches :: Issue -> IO ()
+showMatches issue = do
+ T.putStrLn issue.title
+ T.putStrLn ""
+ T.putStrLn issue.description
-listMatches :: TreeGrepperResult -> IO ()
-listMatches treeGrepperResult =
- mapM_ (putStrLn . unlines . take 1 . lines . (.text)) $ treeGrepperResult.matches
+listMatches :: Issue -> IO ()
+listMatches issue =
+ T.putStrLn issue.title
data UnknownFileExtension = UnknownFileExtension
{ extension :: String
@@ -142,22 +140,10 @@ data InvalidTreeGrepperResult = InvalidTreeGrepperResult
instance Exception InvalidTreeGrepperResult
-forgetGetIssuesExceptions :: UnknownFileExtension -> IO (Maybe _)
-forgetGetIssuesExceptions _ =
- pure Nothing
+forgetGetIssuesExceptions :: UnknownFileExtension -> IO (Maybe a)
+forgetGetIssuesExceptions _ = pure Nothing
-data Issue = Issue {}
-
-data TreeGrepperResult = TreeGrepperResult
- { file :: String,
- file_type :: String,
- matches :: [Match]
- }
- deriving (Show, Generic)
-
-instance A.FromJSON TreeGrepperResult
-
-getIssues :: String -> IO [TreeGrepperResult]
+getIssues :: String -> IO [Issue]
getIssues filename =
let extension = F.takeExtension filename
treeGrepperLanguage =
@@ -180,27 +166,29 @@ getIssues filename =
_ -> throw (UnknownFileExtension extension)
decode raw =
case A.eitherDecode raw of
- Left error ->
- throw (InvalidTreeGrepperResult error)
- Right treeGrepperResult ->
- treeGrepperResult
- in fmap (map fixTreeGrepper) $
- fmap (decode . snd) $
- P.readProcessStdout
- ( String.fromString
- ( "tree-grepper --query '"
- ++ treeGrepperLanguage
- ++ "' '"
- ++ treeGrepperQuery
- ++ "' --format json '"
- ++ filename
- ++ "'"
- )
- )
-
-fixTreeGrepper :: TreeGrepperResult -> TreeGrepperResult
+ Left e -> throw (InvalidTreeGrepperResult e)
+ Right treeGrepperResult -> treeGrepperResult
+ in catMaybes
+ . map (uncurry I.fromMatch)
+ . concatMap (\result -> map ((,) result) result.matches)
+ . map fixTreeGrepper
+ . decode
+ . snd
+ <$> P.readProcessStdout
+ ( String.fromString
+ ( "tree-grepper --query '"
+ ++ treeGrepperLanguage
+ ++ "' '"
+ ++ treeGrepperQuery
+ ++ "' --format json '"
+ ++ filename
+ ++ "'"
+ )
+ )
+
+fixTreeGrepper :: G.Result -> G.Result
fixTreeGrepper treeGrepperResult =
- treeGrepperResult {matches = TM.merge treeGrepperResult.matches}
+ treeGrepperResult {G.matches = G.merge treeGrepperResult.matches}
getFiles :: IO [String]
getFiles =