aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorLibravatar Alexander Foremny <aforemny@posteo.de>2023-11-30 14:39:16 +0100
committerLibravatar Alexander Foremny <aforemny@posteo.de>2023-11-30 14:40:13 +0100
commit4e31ecf2c139455e2d2459ff98f2d4589f7b9dd2 (patch)
tree9ea519319dd58fb419dc833088cd9217beb121c9
parentf82d2c4be5965ae8b4b7dea1d2a00cf8a1f92954 (diff)
chore: make issue ids obligatory
-rw-r--r--app/Issue.hs27
-rw-r--r--app/Issue/Meta.hs3
-rw-r--r--app/Main.hs6
3 files changed, 15 insertions, 21 deletions
diff --git a/app/Issue.hs b/app/Issue.hs
index bcb5333..65afdd6 100644
--- a/app/Issue.hs
+++ b/app/Issue.hs
@@ -8,7 +8,6 @@ module Issue
where
import Data.Binary (Binary)
-import Data.List (find)
import Data.Text qualified as T
import Data.Text.IO qualified as T
import Data.Time.Clock (UTCTime (utctDay))
@@ -36,20 +35,21 @@ data Issue = Issue
}
deriving (Show, Binary, Generic, Eq)
-id :: Issue -> Maybe String
-id issue =
- (\(Tag _ v) -> T.unpack <$> v)
- =<< find (\(Tag k _) -> k == "id") (issue.tags ++ issue.internalTags)
+id :: Issue -> T.Text
+id issue = toSpinalCase issue.title
+ where
+ toSpinalCase = T.replace " " "-" . T.filter keep . T.toLower
+ keep = (`elem` (concat [[' ', '-'], ['a' .. 'z'], ['0' .. '9']]))
internalTags :: Issue -> [Tag]
-internalTags (Issue {..}) =
+internalTags issue@(Issue {..}) =
concat
- [ [ Tag "id" $ Just $ toSpinalCase title,
- Tag "title" $ Just $ title,
+ [ [ Tag "id" $ Just issue.id,
+ Tag "title" $ Just title,
Tag "createdAt" $ Just $ T.pack $ show $ utctDay provenance.first.date,
Tag "modifiedAt" $ Just $ T.pack $ show $ utctDay provenance.last.date,
- Tag "author" $ Just $ provenance.first.author.name,
- Tag "editor" $ Just $ provenance.last.author.name,
+ Tag "author" $ Just provenance.first.author.name,
+ Tag "editor" $ Just provenance.last.author.name,
Tag "state" $ Just $ if closed then "closed" else "open"
],
map (Tag "type" . Just) markers
@@ -58,14 +58,9 @@ internalTags (Issue {..}) =
instance HasField "internalTags" Issue [Tag] where
getField issue = internalTags issue
-instance HasField "id" Issue (Maybe String) where
+instance HasField "id" Issue T.Text where
getField issue = id issue
-toSpinalCase :: T.Text -> T.Text
-toSpinalCase = T.replace " " "-" . T.filter keep . T.toLower
- where
- keep = (`elem` (concat [[' ', '-'], ['a' .. 'z'], ['0' .. '9']]))
-
replaceText :: Issue -> T.Text -> IO ()
replaceText issue s' = T.writeFile issue.file . replace (indent (comment s')) =<< T.readFile issue.file
where
diff --git a/app/Issue/Meta.hs b/app/Issue/Meta.hs
index 4c237a4..19ccab3 100644
--- a/app/Issue/Meta.hs
+++ b/app/Issue/Meta.hs
@@ -4,7 +4,6 @@ module Issue.Meta
)
where
-import Data.Text qualified as T
import Issue (Issue (..))
import Issue.Tag (Tag, tagValue)
@@ -20,7 +19,7 @@ getMeta issues issue =
concatMap
( \issueOther ->
let tagsRelevant =
- filter (\tag -> tagValue tag == fmap T.pack issue.id) issueOther.tags
+ filter (\tag -> tagValue tag == Just issue.id) issueOther.tags
in map (\tag -> (issueOther, tag)) tagsRelevant
)
issues
diff --git a/app/Main.hs b/app/Main.hs
index 70ebf5e..737becc 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -376,7 +376,7 @@ import Data.Function ((&))
import Data.List (find, intersperse, isPrefixOf)
import Data.List.Extra (list)
import Data.Map qualified as M
-import Data.Maybe (catMaybes, maybeToList)
+import Data.Maybe (maybeToList)
import Data.Set qualified as S
import Data.Text qualified as T
import Data.Text.IO qualified as T
@@ -546,7 +546,7 @@ idArg =
O.strArgument
( O.metavar "ID"
<> O.completer
- (O.listIOCompleter $ catMaybes . map I.id . (._3) . last <$> getHistory)
+ (O.listIOCompleter $ map (T.unpack . I.id) . (._3) . last <$> getHistory)
)
editFlag :: O.Parser Bool
@@ -662,7 +662,7 @@ main = do
Options {colorize, width, command = Show {id, edit}} -> do
issues <- (._3) . last <$> getHistory
issue <-
- case find ((==) (Just id) . I.id) issues of
+ case find ((==) id . T.unpack . I.id) issues of
Nothing -> die (printf "no issue with id `%s'\n" id)
Just issue -> pure issue
let meta = I.getMeta issues issue