aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs77
1 files changed, 54 insertions, 23 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 3d71ebc..274bfa4 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -1,14 +1,3 @@
--- TODO Edit issues from command line
---
--- I would like to edit issues from the command line.
---
--- `anissue edit @id` should bring up the issue inside `$EDITOR`, updating the issue with any changes made within `$EDITOR`.
---
--- Comment markers should be stripped, and the file format should be Markdown. Issue markers could be stripped.
---
--- I am personally anticipating that this is used most frequently in response to `anissue show @id`. So, maybe `anissue show @id --edit` should be a synonym?
--- Rationale: the latter is typing `<UP> --edit<CR>`. The former, after show, is typing `<UP><ESC>^wcwedit<CR>`, the former obviously being more palatable.
-
-- TODO Tag improvements (OR-filtering)
--
-- Currently it is not possible to filter for an issue satisfying one filter or another. We could add the following syntax allowing it:
@@ -447,10 +436,10 @@ module Main where
import Control.Applicative ((<|>))
import Data.Function ((&))
-import Issue.Provenance qualified as I
import Data.List (find, isPrefixOf)
import Data.Maybe (catMaybes)
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 Data.Time.Clock (UTCTime (utctDay))
@@ -461,6 +450,7 @@ import Issue (Issue (..))
import Issue qualified as I
import Issue.Filter (Filter, applyFilters)
import Issue.Filter qualified as I
+import Issue.Provenance qualified as I
import Issue.Sort (Sort, applySorts)
import Issue.Sort qualified as I
import Options.Applicative ((<**>))
@@ -471,6 +461,8 @@ import Prettyprinter.Render.Terminal qualified as P
import Process (proc, sh_, textInput)
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.Process.Typed qualified as P
import Text.Printf
import TreeGrepper.Match qualified as G
@@ -550,7 +542,8 @@ data Command
}
| Log
| Show
- { id :: String
+ { id :: String,
+ edit :: Bool
}
deriving (Show)
@@ -580,6 +573,7 @@ showCmd :: O.Parser Command
showCmd =
Show
<$> idArg
+ <*> editFlag
filesArg :: O.Parser [String]
filesArg = O.many (O.strArgument (O.metavar "FILE" <> O.action "file"))
@@ -592,6 +586,13 @@ idArg =
(O.listIOCompleter $ catMaybes . map I.id . fst <$> getHistory)
)
+editFlag :: O.Parser Bool
+editFlag =
+ O.switch
+ ( O.long "edit"
+ <> O.help "Edit issue in $EDITOR."
+ )
+
die :: String -> IO a
die s = do
printf "error: %s\n" s
@@ -655,11 +656,25 @@ main = do
es'
)
(reverse ess')
- Options {colorize, width, command = Show {id}} -> do
+ Options {colorize, width, command = Show {id, edit}} -> do
issues <- fst <$> getHistory
- case find ((==) (Just id) . I.id) issues of
- Nothing -> die (printf "no issue with id `%s'\n" id)
- Just issue -> do
+ issue <-
+ case find ((==) (Just id) . I.id) issues of
+ Nothing -> die (printf "no issue with id `%s'\n" id)
+ Just issue -> pure issue
+ let s =
+ -- TODO Hardcoded issue marker.
+ ("TODO " <> LT.fromStrict issue.title)
+ <> maybe "" (("\n\n" <>) . LT.fromStrict) issue.description
+ if edit
+ then do
+ withSystemTempFile (printf "%s.md" id) $ \fp h -> do
+ LT.hPutStr h s
+ hFlush h
+ hClose h
+ sh_ (proc "${EDITOR-vi} -- %" fp)
+ replaceText issue =<< T.readFile fp
+ else do
-- TODO Make `show` page-able
--
-- We have to set `noPager` unconditionally to `True` for now, as not
@@ -689,12 +704,7 @@ main = do
Nothing -> "mdcat --local"
Just width' -> proc "mdcat --columns % --local" width'
)
- & P.setStdin
- ( textInput
- ( ("# " <> LT.fromStrict issue.title)
- <> maybe "" (("\n\n" <>) . LT.fromStrict) issue.description
- )
- )
+ & P.setStdin (textInput s)
)
putDoc colorize True width $
P.pretty $
@@ -704,6 +714,27 @@ main = do
++ show issue.start.row
++ "\n"
+-- TODO Move `replaceText` to `Issue`
+
+-- TODO `replaceFile` hardcodes comment
+replaceText :: Issue -> T.Text -> IO ()
+replaceText issue s' = T.writeFile issue.file . replace (indent (comment s')) =<< T.readFile issue.file
+ where
+ comment = T.intercalate "\n" . map T.strip . map ("-- " <>) . T.lines
+ indent = T.intercalate "\n" . mapButFirst (T.replicate (issue.start.column - 1) " " <>) . T.lines
+ replace s t = before <> s <> after
+ where
+ t' = T.lines t
+ before = T.intercalate "\n" (mapLast (T.take (issue.start.column - 1)) (take issue.start.row t'))
+ after = T.unlines (mapFirst (T.drop issue.end.column) (drop (issue.end.row - 1) t'))
+ mapFirst _ [] = []
+ mapFirst f (x : xs) = f x : xs
+ mapLast _ [] = []
+ mapLast f [x] = [f x]
+ mapLast f (x : xs) = x : mapLast f xs
+ mapButFirst _ [] = []
+ mapButFirst f (x : xs) = x : map f xs
+
putDoc :: Color -> Bool -> Maybe Int -> P.Doc P.AnsiStyle -> IO ()
putDoc colorize noPager width doc = do
isTty <- (== 1) <$> c_isatty 1