aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorLibravatar Alexander Foremny <aforemny@posteo.de>2023-11-28 13:06:48 +0100
committerLibravatar Alexander Foremny <aforemny@posteo.de>2023-11-28 13:10:07 +0100
commit739c0d06b63bed7619b39eb189c5e5a34fd8da49 (patch)
tree0c4c0f39ccce82f5a325045db3c043c699e5c907
parentc138fb9910c661f7efd00cc7dceb6fc68dc790a9 (diff)
editing issues preserves comment style
-rw-r--r--app/History/PartialCommitInfo.hs7
-rw-r--r--app/Issue.hs9
-rw-r--r--app/Issue/Text.hs39
-rw-r--r--app/TreeGrepper/Comment.hs54
-rw-r--r--app/TreeGrepper/FileType.hs4
5 files changed, 67 insertions, 46 deletions
diff --git a/app/History/PartialCommitInfo.hs b/app/History/PartialCommitInfo.hs
index b37ada5..7497f38 100644
--- a/app/History/PartialCommitInfo.hs
+++ b/app/History/PartialCommitInfo.hs
@@ -99,13 +99,14 @@ fromComment cwd comment = do
end = comment.end,
tags = maybe [] I.extractTags description,
markers = markers,
- rawText = rawText
+ rawText = rawText,
+ commentStyle = commentStyle
}
else Nothing
)
where
- rawText = comment.text
- (title', description) = I.extractText comment.file_type rawText
+ (commentStyle, rawText) = G.uncomment comment.file_type comment.text
+ (title', description) = I.extractText rawText
(markers, title) = I.stripIssueMarkers title'
dieOfInvalidTreeGrepperResult :: E.InvalidTreeGrepperResult -> IO a
diff --git a/app/Issue.hs b/app/Issue.hs
index 411e910..73122ef 100644
--- a/app/Issue.hs
+++ b/app/Issue.hs
@@ -16,6 +16,7 @@ import GHC.Generics (Generic)
import GHC.Records (HasField (..))
import Issue.Provenance (Author (..), Commit (..), Provenance (..))
import Issue.Tag (Tag (..))
+import TreeGrepper.Comment qualified as G
import TreeGrepper.Match qualified as G
import Prelude hiding (id)
@@ -28,7 +29,8 @@ data Issue = Issue
end :: G.Position,
tags :: [Tag],
markers :: [T.Text],
- rawText :: T.Text
+ rawText :: T.Text,
+ commentStyle :: G.CommentStyle
}
deriving (Show, Binary, Generic, Eq)
@@ -58,13 +60,10 @@ toSpinalCase = T.replace " " "-" . T.filter keep . T.toLower
where
keep = (`elem` (concat [[' ', '-'], ['a' .. 'z'], ['0' .. '9']]))
--- TODO `replaceFile` hardcodes comment
---
--- @difficulty easy
replaceText :: Issue -> T.Text -> IO ()
replaceText issue s' = T.writeFile issue.file . replace (indent (comment s')) =<< T.readFile issue.file
where
- comment = T.intercalate "\n" . map T.strip . map ("-- " <>) . T.lines
+ comment = T.intercalate "\n" . map T.strip . T.lines . G.comment issue.commentStyle
indent = T.intercalate "\n" . mapButFirst (T.replicate (issue.start.column - 1) " " <>) . T.lines
replace s t = before <> s <> after
where
diff --git a/app/Issue/Text.hs b/app/Issue/Text.hs
index 5d1dddb..4cfc5f7 100644
--- a/app/Issue/Text.hs
+++ b/app/Issue/Text.hs
@@ -6,52 +6,17 @@ module Issue.Text
where
import Control.Arrow (first, second)
-import Data.List (find)
-import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Text qualified as T
-import TreeGrepper.FileType (FileType)
-import TreeGrepper.FileType qualified as G
-extractText :: FileType -> Text -> (Text, Maybe Text)
-extractText fileType rawText = (title, description)
+extractText :: Text -> (Text, Maybe Text)
+extractText text = (title, description)
where
- text = stripComments fileType $ stripLines rawText
- stripLines = T.intercalate "\n" . map T.strip . T.lines
(title, description') = second T.stripStart $ T.breakOn "\n" text
description
| T.null description' = Nothing
| otherwise = Just description'
-stripComments :: G.FileType -> Text -> Text
-stripComments fileType text =
- maybe
- (stripLineComments (G.info fileType).lineStart text)
- ( \(blockInfo, blockStart) ->
- stripBlockComment blockStart blockInfo.blockEnd text
- )
- $ do
- blockInfo <- (G.info fileType).block
- (,) blockInfo <$> find (`T.isPrefixOf` text) blockInfo.blockStart
-
-stripLineComments :: Text -> Text -> Text
-stripLineComments lineStart text =
- onLines
- ( \line ->
- fromMaybe line . fmap T.stripStart $
- T.stripPrefix lineStart line
- )
- text
- where
- onLines f = T.intercalate "\n" . map f . T.lines
-
-stripBlockComment :: Text -> Text -> Text -> Text
-stripBlockComment blockStart blockEnd text =
- T.strip
- . (fromMaybe text . T.stripSuffix blockEnd)
- . (fromMaybe text . T.stripPrefix blockStart)
- $ text
-
issueMarkers :: [T.Text]
issueMarkers =
[ "TODO",
diff --git a/app/TreeGrepper/Comment.hs b/app/TreeGrepper/Comment.hs
index 1a6aed2..0ca9543 100644
--- a/app/TreeGrepper/Comment.hs
+++ b/app/TreeGrepper/Comment.hs
@@ -1,13 +1,19 @@
module TreeGrepper.Comment
( Comment (..),
getComments,
+ CommentStyle (..),
+ uncomment,
+ comment,
)
where
import Control.Exception (throw)
import Data.Aeson qualified as A
+import Data.Binary (Binary)
import Data.ByteString.Lazy.Char8 qualified as B
import Data.Function ((&))
+import Data.List (find)
+import Data.Maybe (fromMaybe)
import Data.Text qualified as T
import Exception qualified as E
import GHC.Generics (Generic)
@@ -15,6 +21,7 @@ import Process (proc, sh)
import System.FilePath (takeExtension)
import System.Process.Typed (setWorkingDir)
import TreeGrepper.FileType (FileType (..))
+import TreeGrepper.FileType qualified as G
import TreeGrepper.Match (Match (..), Position (..))
import TreeGrepper.Match qualified as G
import TreeGrepper.Result (Result (..))
@@ -33,6 +40,53 @@ data Comment = Comment
}
deriving (Show, Generic)
+data CommentStyle
+ = LineStyle T.Text
+ | BlockStyle T.Text T.Text
+ deriving (Eq, Show, Generic, Binary)
+
+comment :: CommentStyle -> T.Text -> T.Text
+comment (LineStyle linePrefix) = T.unlines . map ((linePrefix <> " ") <>) . T.lines
+comment (BlockStyle blockStart blockEnd) = (blockStart <>) . (<> blockEnd)
+
+uncomment :: FileType -> T.Text -> (CommentStyle, T.Text)
+uncomment fileType rawText =
+ maybe
+ ( ( LineStyle info.lineStart,
+ stripLineComments (G.info fileType).lineStart text
+ )
+ )
+ ( \(blockInfo, blockStart) ->
+ ( BlockStyle blockStart blockInfo.blockEnd,
+ stripBlockComment blockStart blockInfo.blockEnd text
+ )
+ )
+ $ do
+ blockInfo <- info.block
+ (,) blockInfo <$> find (`T.isPrefixOf` text) blockInfo.blockStart
+ where
+ info = G.info fileType
+ text = stripLines rawText
+ stripLines = T.intercalate "\n" . map T.strip . T.lines
+
+stripLineComments :: T.Text -> T.Text -> T.Text
+stripLineComments lineStart text =
+ onLines
+ ( \line ->
+ fromMaybe line . fmap T.stripStart $
+ T.stripPrefix lineStart line
+ )
+ text
+ where
+ onLines f = T.intercalate "\n" . map f . T.lines
+
+stripBlockComment :: T.Text -> T.Text -> T.Text -> T.Text
+stripBlockComment blockStart blockEnd text =
+ T.strip
+ . (fromMaybe text . T.stripSuffix blockEnd)
+ . (fromMaybe text . T.stripPrefix blockStart)
+ $ text
+
fromMatch :: Result -> Match -> Comment
fromMatch Result {..} Match {..} = Comment {..}
diff --git a/app/TreeGrepper/FileType.hs b/app/TreeGrepper/FileType.hs
index 1ebeac1..506cbc5 100644
--- a/app/TreeGrepper/FileType.hs
+++ b/app/TreeGrepper/FileType.hs
@@ -8,7 +8,9 @@ module TreeGrepper.FileType
where
import Data.Aeson (FromJSON (parseJSON))
+import Data.Binary (Binary)
import Data.Text (Text)
+import GHC.Generics (Generic)
import Prelude hiding (all)
data FileType
@@ -16,7 +18,7 @@ data FileType
| Haskell
| Nix
| Shell
- deriving (Show)
+ deriving (Eq, Show, Generic, Binary)
instance FromJSON FileType where
parseJSON v =