aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
diff options
context:
space:
mode:
authorLibravatar Alexander Foremny <aforemny@posteo.de>2024-02-29 04:11:10 +0100
committerLibravatar Alexander Foremny <aforemny@posteo.de>2024-03-01 06:45:13 +0100
commit9a49ec0dcd6f75736949350844f85d80fe48a662 (patch)
treeb506bb61f4951207aa1aff04080fd3d7874927c3 /app/Main.hs
parent941f0d4ccb688d42c0438e05051ed78a410431b6 (diff)
wip: add `review` command
Prototype of the `review` command, cf. `anissue review -h`. Also adds the `status` command.
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs64
1 files changed, 63 insertions, 1 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 52a316d..5d29923 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -1,5 +1,5 @@
-- TODO Compute history from the top
---
+-- _
-- Currently we are computing the history from the bottom (ie. earliest commit
-- first). When computing history from the top, it might allow us to interrupt
-- the process and present slightly inaccurate information earlier.
@@ -319,6 +319,7 @@ module Main where
import Comment qualified as G
import Control.Applicative ((<|>))
+import Control.Exception (catch)
import Data.Function ((&))
import Data.List (find, intersperse)
import Data.Map qualified as M
@@ -327,6 +328,7 @@ import Data.Text qualified as T
import Data.Text.IO qualified as T
import Data.Text.Lazy qualified as LT
import Data.Text.Lazy.IO qualified as LT
+import Exception qualified as E
import Git qualified
import History qualified as H
import Issue (Issue (..))
@@ -341,7 +343,9 @@ import Options.Applicative qualified as O
import Process (proc, sh_, textInput)
import Render ((<<<))
import Render qualified as P
+import Review qualified as R
import Settings (Settings (..), readSettings)
+import Status qualified as S
import System.Console.Terminal.Size qualified as Terminal
import System.Exit (ExitCode (ExitFailure), exitWith)
import System.FilePath ((</>))
@@ -424,6 +428,12 @@ data Command
| Open
{ id :: String
}
+ | Status
+ | Review
+ { baseBranch :: T.Text,
+ featureBranch :: T.Text,
+ granularity :: R.Granularity
+ }
| Search
{ pattern :: R.RE,
closed :: Bool,
@@ -444,10 +454,14 @@ cmd =
O.progDesc "Show a log of all issues",
O.command "open" . O.info openCmd $
O.progDesc "Open file containing an issue",
+ O.command "review" . O.info reviewCmd $
+ O.progDesc "Review changes",
O.command "search" . O.info searchCmd $
O.progDesc "List issues matching a pattern",
O.command "show" . O.info showCmd $
O.progDesc "Show details of all issues",
+ O.command "status" . O.info statusCmd $
+ O.progDesc "Describe the current anissue action.",
O.command "tags" . O.info tagsCmd $
O.progDesc "Show all tags"
]
@@ -480,6 +494,36 @@ openCmd =
Open
<$> idArg
+reviewCmd :: O.Parser Command
+reviewCmd =
+ Review
+ <$> baseBranchArg
+ <*> featureBranchArg
+ <*> granularityArg
+
+baseBranchArg :: O.Parser T.Text
+baseBranchArg =
+ O.option O.auto $
+ O.long "base"
+ <> O.short 'b'
+ <> O.metavar "BRANCH"
+ <> O.help "Base branch from which to review changes. Defaults to `main`."
+ <> O.value "main"
+
+featureBranchArg :: O.Parser T.Text
+featureBranchArg =
+ O.strArgument (O.metavar "BRANCH_NAME" <> O.value "HEAD")
+
+granularityArg :: O.Parser R.Granularity
+granularityArg =
+ O.option
+ O.auto
+ ( O.long "granularity"
+ <> O.metavar "GRANULARITY"
+ <> O.help "Granularity of the review. One of `as-one`, `per-commit`, `per-file` or `per-hunk`. Default: `as-one`."
+ <> O.value R.AsOne
+ )
+
showCmd :: O.Parser Command
showCmd =
Show
@@ -492,6 +536,10 @@ patternArg =
(O.maybeReader R.compileRegex)
(O.metavar "PATTERN")
+statusCmd :: O.Parser Command
+statusCmd =
+ pure Status
+
tagsCmd :: O.Parser Command
tagsCmd =
pure Tags
@@ -548,6 +596,20 @@ main :: IO ()
main = do
settings <- readSettings
O.execParser (O.info (options <**> O.helper) O.idm) >>= \case
+ Options {colorize, noPager, width, command = Status} -> do
+ status <- S.readStatus ".anissue/status"
+ putDoc colorize noPager width status
+ Options {colorize, noPager, width, command = Review {baseBranch, featureBranch, granularity}} -> do
+ sh_ "test -z $(git status --porcelain --untracked-files=no)"
+ `catch` \(_ :: E.ProcessException) ->
+ error "working directory not clean, aborting.."
+ S.withReviewing
+ (putDoc colorize noPager width)
+ granularity
+ baseBranch
+ featureBranch
+ ".anissue/status"
+ S.continueReview
Options {colorize, noPager, width, command = List {sort, filters, files, group = Just group, closed}} -> do
ungroupedIssues <-
I.applySorts sort