aboutsummaryrefslogtreecommitdiffstats
path: root/app/Issue.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Issue.hs')
-rw-r--r--app/Issue.hs27
1 files changed, 11 insertions, 16 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