aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs58
1 files changed, 25 insertions, 33 deletions
diff --git a/app/Main.hs b/app/Main.hs
index a7901bd..3bb60e2 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -447,18 +447,20 @@ module Main where
import Control.Applicative ((<|>))
import Data.Function ((&))
-import Data.List (find)
+import Data.List (find, isPrefixOf)
import Data.Maybe (catMaybes)
import Data.Text qualified as T
import Data.Text.Lazy qualified as LT
import Data.Text.Lazy.IO qualified as LT
import Data.Time.Clock (UTCTime (utctDay))
-import History (IssueEvent (..), listEvents, listIssues)
+import History (getHistory)
+import History.CommitHash qualified as CH
+import History.IssueEvent (IssueEvent (..))
import Issue (Issue (..))
import Issue qualified as I
-import Issue.Filter (Filter)
+import Issue.Filter (Filter, applyFilters)
import Issue.Filter qualified as I
-import Issue.Sort (Sort)
+import Issue.Sort (Sort, applySorts)
import Issue.Sort qualified as I
import Options.Applicative ((<**>))
import Options.Applicative qualified as O
@@ -586,9 +588,7 @@ idArg =
O.strArgument
( O.metavar "ID"
<> O.completer
- ( O.listIOCompleter $
- catMaybes . map I.id <$> listIssues [] [] []
- )
+ (O.listIOCompleter $ catMaybes . map I.id . fst <$> getHistory)
)
die :: String -> IO a
@@ -600,7 +600,8 @@ main :: IO ()
main = do
O.execParser (O.info (options <**> O.helper) O.idm) >>= \case
Options {colorize, noPager, width, command = List {sort, filters, files}} -> do
- issues <- listIssues sort filters files
+ let withinPath issue = if null files then True else any (\file -> file `isPrefixOf` issue.file) files
+ issues <- applySorts sort . applyFilters filters . filter withinPath . fst <$> getHistory
putDoc colorize noPager width . P.vsep $
map
( \issue ->
@@ -633,34 +634,25 @@ main = do
)
issues
Options {colorize, noPager, width, command = Log} -> do
- -- TODO Reconcile log
- --
- -- When viewing the log I am confused by
- --
- -- (1) lots of sequential commits "changing" the same one issue, but no
- -- others,
- -- (2) having unknown hashes interleaved
- --
- -- I would assume changes to be less frequent, or, if no changes are
- -- considered changes, the log output sorted by hashes (and not
- -- commits?). I would expect only the first commit hash to be unknown.
- --
- -- Thoughts? :-)
- es <- concat <$> listEvents
+ (_, ess') <- getHistory
putDoc colorize noPager width . P.vsep $
- map
- ( \e ->
- let shortHash = P.annotate (P.color P.Yellow) . P.pretty $ maybe "UNKNOWN" (T.take 7) e.hash
- kwd = P.annotate (P.color P.Green) . P.pretty . T.pack
- title issue = P.annotate (P.color P.Blue) . P.annotate P.bold $ P.pretty issue.title
- in case e of
- IssueCreated {issue} -> shortHash <+> kwd "created" <+> title issue
- IssueChanged {issue} -> shortHash <+> kwd "changed" <+> title issue
- IssueDeleted {} -> shortHash <+> kwd "deleted"
+ concatMap
+ ( \(hash, es') ->
+ let shortHash = P.annotate (P.color P.Yellow) . P.pretty $ CH.toShortText hash
+ in map
+ ( \e ->
+ let kwd = P.annotate (P.color P.Green) . P.pretty . T.pack
+ title issue = P.annotate (P.color P.Blue) . P.annotate P.bold $ P.pretty issue.title
+ in case e of
+ IssueCreated {issue} -> shortHash <+> kwd "created" <+> title issue
+ IssueChanged {issue} -> shortHash <+> kwd "changed" <+> title issue
+ IssueDeleted {issue} -> shortHash <+> kwd "deleted" <+> title issue
+ )
+ es'
)
- es
+ (reverse ess')
Options {colorize, width, command = Show {id}} -> do
- issues <- listIssues [] [] []
+ issues <- fst <$> getHistory
case find ((==) (Just id) . I.id) issues of
Nothing -> die (printf "no issue with id `%s'\n" id)
Just issue -> do