{-# LANGUAGE OverloadedRecordDot #-} {-# LANGUAGE OverloadedStrings #-} module History (getIssues, InvalidTreeGrepperResult (..), UnknownFileExtension (..), listIssues) where import Control.Exception (Exception, catch, handle, throw) import Data.Aeson (eitherDecode) import Data.Binary (Binary, decodeFile, encodeFile) import Data.ByteString.Lazy.Char8 qualified as L8 import Data.Function ((&)) import Data.List (intercalate) import Data.Maybe (catMaybes, mapMaybe) import Data.String (fromString) import Data.Text (Text, lines, unpack) import Data.Text.Encoding (decodeUtf8) import Issue (Issue (..), fromMatch, id) import Issue.Filter (Filter, applyFilter) import Parallel (parMapM) import Process (quote, sh, sh_) import System.Directory (createDirectoryIfMissing, doesFileExist, getCurrentDirectory) import System.Exit (ExitCode (ExitFailure), exitWith) import System.FilePath (takeExtension, ()) import System.IO.Temp (withSystemTempDirectory) import System.Process.Typed (setWorkingDir) import Text.Printf (printf) import TreeGrepper.Match qualified as G import TreeGrepper.Result qualified as G import Prelude hiding (id, lines) import Prelude qualified as Prelude data UnknownFileExtension = UnknownFileExtension { extension :: String } deriving (Show) instance Exception UnknownFileExtension data InvalidTreeGrepperResult = InvalidTreeGrepperResult { error :: String } deriving (Show) instance Exception InvalidTreeGrepperResult listIssues :: [Filter] -> [FilePath] -> IO [Issue] listIssues filters paths = do commits <- getCommits currentIssues <- listIssuesCurrent paths historicalIssues <- fmap concat $ parMapM (\commit -> cached commit (\_ -> listIssuesOf commit)) commits let currentIssuesFiltered = filter (applyFilter filters) currentIssues pure $ map (fixProvenance historicalIssues) currentIssuesFiltered getCommits :: IO [Text] getCommits = fmap (lines . decodeUtf8 . L8.toStrict) $ sh ("git log --format=%H") fixProvenance :: [Issue] -> Issue -> Issue fixProvenance historicalIssues = merge . pick historicalIssues pick :: [Issue] -> Issue -> (Issue, [Issue]) pick issues issue = (issue, filter (isSameIssue) issues) where isSameIssue otherIssue = id otherIssue == id issue merge :: (Issue, [Issue]) -> Issue merge (issue, issues) = case (mapMaybe provenance (reverse issues)) of [] -> issue provenance : _ -> issue {provenance = Just provenance} listIssuesCurrent :: [FilePath] -> IO [Issue] listIssuesCurrent paths = do worktree <- getCurrentDirectory files <- getFiles worktree paths concat <$> (catch (getIssuesPar worktree files) (\(InvalidTreeGrepperResult e) -> die e)) listIssuesOf :: Text -> IO [Issue] listIssuesOf commit = do withSystemTempDirectory "history" $ \tmp -> do worktree <- do let worktree = tmp unpack commit sh_ (fromString (printf "git worktree add --detach %s %s" (quote worktree) (quote (unpack commit)))) pure worktree files <- getFilesChanged worktree concat <$> catch (getIssuesPar worktree files) (\(InvalidTreeGrepperResult e) -> die e) forgetGetIssuesExceptions :: UnknownFileExtension -> IO [a] forgetGetIssuesExceptions _ = pure [] getFiles :: FilePath -> [String] -> IO [FilePath] getFiles cwd paths = Prelude.lines . L8.unpack <$> sh ( fromString ( (printf "git ls-files --cached --exclude-standard --other%s") ( case paths of [] -> "" _ -> " -- " ++ intercalate " " (map quote paths) ) ) & setWorkingDir cwd ) getFilesChanged :: FilePath -> IO [FilePath] getFilesChanged cwd = Prelude.lines . L8.unpack <$> sh ( "git show -p --name-only --format=''" & setWorkingDir cwd ) getIssuesPar :: FilePath -> [FilePath] -> IO [[Issue]] getIssuesPar worktree = parMapM (handle forgetGetIssuesExceptions . getIssues worktree) getIssues :: FilePath -> FilePath -> IO [Issue] getIssues cwd filename = do let extension = takeExtension filename treeGrepperLanguage = -- TODO Add support for all tree-grepper supported files -- -- tree-grepper supported files can be listed through `tree-grepper -- --languages`. case extension of ".elm" -> "elm" ".hs" -> "haskell" ".nix" -> "nix" ".sh" -> "sh" _ -> throw (UnknownFileExtension extension) treeGrepperQuery = case extension of ".elm" -> "([(line_comment) (block_comment)])" ".hs" -> "(comment)" ".nix" -> "(comment)" ".sh" -> "(comment)" _ -> throw (UnknownFileExtension extension) decode raw = case eitherDecode raw of Left e -> throw (InvalidTreeGrepperResult e) Right treeGrepperResult -> treeGrepperResult matches <- concatMap (\result -> map ((,) result) result.matches) . map fixTreeGrepper . decode <$> sh ( fromString ( printf "tree-grepper --query %s %s --format json %s" (quote treeGrepperLanguage) (quote treeGrepperQuery) (quote filename) ) & setWorkingDir cwd ) catMaybes <$> mapM (uncurry (fromMatch cwd)) matches fixTreeGrepper :: G.Result -> G.Result fixTreeGrepper treeGrepperResult = treeGrepperResult {G.matches = G.merge treeGrepperResult.matches} cached :: Binary a => Text -> (Text -> IO a) -> IO a cached commit func = do cwd <- getCurrentDirectory createDirectoryIfMissing True (cwd ++ "/.anissue") let file = (cwd ++ "/.anissue/" ++ unpack commit) fileExists <- doesFileExist file if fileExists then decodeFile file else do blob <- func commit encodeFile file blob pure blob die :: String -> IO a die s = do printf "error: %s\n" s exitWith (ExitFailure 1)