aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs60
1 files changed, 35 insertions, 25 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 928f1c4..ea9077b 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -364,13 +364,16 @@ module Main where
import Control.Applicative ((<|>))
import Data.Function ((&))
-import Data.List (intersperse)
+import Data.List (find, intersperse)
import Data.Map qualified as M
+import Data.Maybe (fromMaybe)
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 Git qualified
import History (History (..), getHistory)
+import History qualified as H
import Issue (Issue (..))
import Issue qualified as I
import Issue.Filter qualified as I
@@ -386,8 +389,8 @@ import Render qualified as P
import Settings (Settings (..), readSettings)
import System.Console.Terminal.Size qualified as Terminal
import System.Exit (ExitCode (ExitFailure), exitWith)
-import System.IO (hClose, hFlush)
-import System.IO.Temp (withSystemTempFile)
+import System.FilePath ((</>))
+import System.IO.Temp (withSystemTempDirectory)
import System.Process.Typed qualified as P
import Text.Printf
import Tuple ()
@@ -465,24 +468,14 @@ data Command
sort :: [I.Sort],
group :: Maybe T.Text,
closed :: Bool,
- detailed :: Bool
+ detailed :: Bool,
+ edit :: Bool
}
| Log
{ patch :: Bool
}
| Show
{ id :: String,
- -- TODO Extend `--edit` to `List` command
- --
- -- Similarly to `anissue show --edit`, `anisuse list --edit` should open all selected (ie. through `--filter`) issues an `$EDITOR`.
- --
- -- This would allow for instance for triaging issues once a week:
- --
- -- ```
- -- anissue list --filter '@createdAt <1w' --edit
- -- ```
- --
- -- \*Note that `<1w` is hypothetical syntax, currenlty.*
edit :: Bool
}
| Tags
@@ -509,6 +502,7 @@ listCmd =
<*> I.groupArg
<*> closedArg
<*> detailedArg
+ <*> editFlag
logCmd :: O.Parser Command
logCmd =
@@ -587,7 +581,7 @@ main = do
<$> getHistory
let groupedIssues = I.groupIssuesByTag group ungroupedIssues
putDoc colorize noPager width (group, groupedIssues)
- Options {colorize, noPager, width, command = List {sort, filters, files, group = Nothing, closed, detailed}} -> do
+ Options {colorize, noPager, width, command = List {sort, filters, files, group = Nothing, closed, detailed, edit}} -> do
issues <-
I.applySorts sort
. I.applyFilters filters
@@ -595,8 +589,11 @@ main = do
. I.applyClosed closed
. (M.elems . (.issues))
<$> getHistory
- putDoc colorize noPager width . (P.vsep . intersperse "") $
- map (if detailed then (P.render . P.Detailed) else (P.render . P.Summarized)) issues
+ if edit
+ then editIssues issues
+ else
+ putDoc colorize noPager width . (P.vsep . intersperse "") $
+ map (if detailed then (P.render . P.Detailed) else (P.render . P.Summarized)) issues
Options {colorize, noPager, width, command = Log {patch}} -> do
es <- reverse . (.issueEvents) <$> getHistory
putDoc colorize noPager width $
@@ -610,13 +607,7 @@ main = do
Nothing -> die (printf "no issue with id `%s'\n" id)
Just issue -> pure issue
if edit
- then do
- withSystemTempFile (printf "%s.md" id) $ \fp h -> do
- T.hPutStr h (issue.rawText)
- hFlush h
- hClose h
- sh_ (proc "${EDITOR-vi} -- %" fp)
- I.replaceText issue =<< T.readFile fp
+ then editIssues [issue]
else putDoc colorize noPager width $ showIssue (M.elems issues) issue
Options {colorize, noPager, width, internalTags, command = Tags} -> do
issues <- (.issues) <$> getHistory
@@ -639,6 +630,25 @@ showIssue issues issue = do
<<< ("\n" :: T.Text)
<<< meta
+editIssues :: [Issue] -> IO ()
+editIssues issues = withSystemTempDirectory "anissue-edit" (go issues)
+ where
+ go :: [Issue] -> FilePath -> IO ()
+ go issues cwd = do
+ mapM_ (\issue -> T.writeFile (fp issue) issue.rawText) issues
+ sh_ (proc "${EDITOR-vi} -- %" (map fp issues))
+ replaceTexts issues
+ where
+ fp issue = cwd </> (T.unpack issue.id <> ".md")
+
+ replaceTexts [] = pure ()
+ replaceTexts [issue] = do
+ I.replaceText issue =<< T.readFile (fp issue)
+ replaceTexts (issue : issues) = do
+ I.replaceText issue =<< T.readFile (fp issue)
+ issues' <- H.getIssues Git.WorkingTree issue.file
+ replaceTexts [fromMaybe issue (find ((==) issue.id . (.id)) issues') | issue <- issues]
+
putDoc :: P.Render a => Color -> Bool -> Maybe Int -> a -> IO ()
putDoc colorize noPager width renderable = do
isTty <- (== 1) <$> c_isatty 1