aboutsummaryrefslogtreecommitdiffstats
path: root/app/Issue.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Issue.hs')
-rw-r--r--app/Issue.hs67
1 files changed, 51 insertions, 16 deletions
diff --git a/app/Issue.hs b/app/Issue.hs
index 2674a7c..e37c20e 100644
--- a/app/Issue.hs
+++ b/app/Issue.hs
@@ -3,25 +3,29 @@
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
-module Issue (Issue (..), fromMatch, id) where
+module Issue (Issue (..), Provenance (..), fromMatch, id) where
+import Data.ByteString.Lazy.Char8 (unpack)
import Data.List (find, foldl')
+import Data.String (fromString)
import Data.Text (Text)
import Data.Text qualified as T
import Issue.Tag (Tag (..))
import Issue.Tag qualified as I
import Issue.Text qualified as I
+import Process (quote, sh)
+import Text.Printf (printf)
import TreeGrepper.Match (Match (..))
import TreeGrepper.Match qualified as G
import TreeGrepper.Result (Result (..))
import TreeGrepper.Result qualified as G
import Prelude hiding (id)
-import Process qualified as P
data Issue = Issue
{ title :: Text,
description :: Maybe Text,
file :: String,
+ provenance :: Provenance,
start :: G.Position,
end :: G.Position,
tags :: [Tag],
@@ -29,6 +33,11 @@ data Issue = Issue
}
deriving (Show)
+data Provenance = Provenance
+ { firstCommit :: Maybe String
+ }
+ deriving (Show)
+
id :: Issue -> Maybe String
id issue =
(\(Tag _ v) -> T.unpack v)
@@ -36,21 +45,47 @@ id issue =
issue.tags ++ issue.internalTags
)
-fromMatch :: G.Result -> G.Match -> Maybe Issue
-fromMatch result match =
- if any (\marker -> T.isPrefixOf marker title') issueMarkers
- then
- Just
- Issue
- { title = title,
- description = description,
- file = result.file,
- start = match.start,
- end = match.end,
- tags = maybe [] I.extractTags description,
- internalTags = I.internalTags title
+fromMatch :: G.Result -> G.Match -> IO (Maybe Issue)
+fromMatch result match = do
+ firstCommits <-
+ fmap (lines . unpack) $
+ sh $
+ ( fromString
+ ( printf
+ "git --no-pager log --reverse -S\"$(cat %s | tail -n+%d | head -%d)\" --format=%%H -- %s"
+ (quote result.file)
+ match.start.row
+ (match.end.row - match.start.row + 1)
+ (quote result.file)
+ )
+ )
+ let firstCommit =
+ case firstCommits of
+ [] ->
+ Nothing
+ firstCommit' : _ ->
+ Just firstCommit'
+
+ provenance =
+ Provenance
+ { firstCommit = firstCommit
}
- else Nothing
+ pure
+ ( if any (\marker -> T.isPrefixOf marker title') issueMarkers
+ then
+ Just
+ Issue
+ { title = title,
+ description = description,
+ file = result.file,
+ provenance = provenance,
+ start = match.start,
+ end = match.end,
+ tags = maybe [] I.extractTags description,
+ internalTags = I.internalTags title
+ }
+ else Nothing
+ )
where
(title', description) = I.extractText result.file_type match.text
title = stripIssueMarkers title'