;ui: refactor editFileAtPositionCommand (#1359)
This commit is contained in:
parent
d9738dd633
commit
66acb2c317
@ -1,7 +1,5 @@
|
|||||||
{- | Editor integration. -}
|
{- | Editor integration. -}
|
||||||
|
|
||||||
-- {-# LANGUAGE OverloadedStrings #-}
|
|
||||||
|
|
||||||
module Hledger.UI.Editor (
|
module Hledger.UI.Editor (
|
||||||
-- TextPosition
|
-- TextPosition
|
||||||
endPosition
|
endPosition
|
||||||
@ -11,6 +9,8 @@ module Hledger.UI.Editor (
|
|||||||
where
|
where
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
|
import Data.List (intercalate)
|
||||||
|
import Data.Maybe (catMaybes)
|
||||||
import Safe
|
import Safe
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import System.Exit
|
import System.Exit
|
||||||
@ -43,58 +43,58 @@ runEditor mpos f = editFileAtPositionCommand mpos f >>= runCommand >>= waitForPr
|
|||||||
-- | Get a shell command line to open the user's preferred text editor
|
-- | Get a shell command line to open the user's preferred text editor
|
||||||
-- (or a default editor) on the given file, and to focus it at the
|
-- (or a default editor) on the given file, and to focus it at the
|
||||||
-- given text position if one is provided and if we know how.
|
-- given text position if one is provided and if we know how.
|
||||||
-- We know how to focus on position for: emacs, vi, nano.
|
-- We know how to focus on position for: emacs, vi, nano, VS code.
|
||||||
-- We know how to focus on last line for: vi.
|
-- We know how to focus on last line for: vi.
|
||||||
--
|
--
|
||||||
-- Some tests: With line and column numbers specified,
|
-- Some tests:
|
||||||
-- @
|
-- @
|
||||||
-- if EDITOR is: the command should be:
|
-- EDITOR program is: LINE/COL specified ? Command should be:
|
||||||
-- ------------- -----------------------------------
|
-- ------------------ -------------------- -----------------------------------
|
||||||
-- notepad notepad FILE
|
-- emacs, emacsclient LINE COL emacs +LINE:COL FILE
|
||||||
-- vi vi +LINE FILE
|
-- LINE emacs +LINE FILE
|
||||||
-- vi + FILE # negative LINE
|
-- emacs FILE
|
||||||
-- emacs emacs +LINE:COL FILE
|
--
|
||||||
-- emacs FILE # negative LINE
|
-- nano LINE COL nano +LINE,COL FILE
|
||||||
-- (unset) emacsclient -a '' -nw +LINE:COL FILE
|
-- LINE nano +LINE FILE
|
||||||
-- emacsclient -a '' -nw FILE # negative LINE
|
-- nano FILE
|
||||||
|
--
|
||||||
|
-- vi, & variants LINE [COL] vi +LINE FILE
|
||||||
|
-- LINE (negative) vi + FILE
|
||||||
|
-- vi FILE
|
||||||
|
--
|
||||||
|
-- (other PROG) [LINE [COL]] PROG FILE
|
||||||
|
--
|
||||||
|
-- (not set) LINE COL emacsclient -a '' -nw +LINE:COL FILE
|
||||||
|
-- LINE emacsclient -a '' -nw +LINE FILE
|
||||||
|
-- emacsclient -a '' -nw FILE
|
||||||
-- @
|
-- @
|
||||||
--
|
--
|
||||||
-- How to open editors at the last line of a file:
|
-- Notes on opening editors at the last line of a file:
|
||||||
-- @
|
-- @
|
||||||
-- emacs: emacs FILE -f end-of-buffer
|
-- emacs: emacs FILE -f end-of-buffer # (-f must appear after FILE, +LINE:COL must appear before)
|
||||||
-- emacsclient: can't
|
-- emacsclient: can't
|
||||||
-- vi: vi + FILE
|
-- vi: vi + FILE
|
||||||
-- @
|
-- @
|
||||||
--
|
--
|
||||||
editFileAtPositionCommand :: Maybe TextPosition -> FilePath -> IO String
|
editFileAtPositionCommand :: Maybe TextPosition -> FilePath -> IO String
|
||||||
editFileAtPositionCommand mpos f = do
|
editFileAtPositionCommand mpos f = do
|
||||||
let f' = singleQuoteIfNeeded f
|
cmd <- getEditCommand
|
||||||
editcmd <- getEditCommand
|
let
|
||||||
let editor = lowercase $ takeFileName $ headDef "" $ words' editcmd
|
editor = lowercase $ takeFileName $ headDef "" $ words' cmd
|
||||||
let positionarg =
|
f' = singleQuoteIfNeeded f
|
||||||
case mpos of
|
ml = show.fst <$> mpos
|
||||||
Just (l, mc)
|
mc = maybe Nothing (fmap show.snd) mpos :: Maybe String
|
||||||
| editor `elem` [
|
args = case editor of
|
||||||
"ex",
|
e | e `elem` ["emacs", "emacsclient"] -> ['+' : join ":" [ml,mc], f']
|
||||||
"vi","vim","view","nvim","evim","eview",
|
e | e `elem` ["nano"] -> ['+' : join "," [ml,mc], f']
|
||||||
"gvim","gview","rvim","rview","rgvim","rgview"
|
e | e `elem` ["vi","vim","view","nvim","evim","eview","gvim","gview","rvim","rview",
|
||||||
] -> plusAndMaybeLine l mc
|
"rgvim","rgview","ex"] -> [maybe "" plusMaybeLine ml, f']
|
||||||
Just (l, mc)
|
_ -> [f']
|
||||||
| editor `elem` ["emacs", "emacsclient"] -> plusLineAndMaybeColonColumnOrEnd l mc
|
|
||||||
Just (l, mc)
|
|
||||||
| editor `elem` ["nano"] -> plusLineAndMaybeCommaColumn l mc
|
|
||||||
_ -> ""
|
|
||||||
where
|
where
|
||||||
plusAndMaybeLine l _ = "+" ++ if l >= 0 then show l else ""
|
join sep = intercalate sep . catMaybes
|
||||||
plusLineAndMaybeCommaColumn l mc = "+" ++ show l ++ maybe "" ((","++).show) mc
|
plusMaybeLine l = "+" ++ if take 1 l == "-" then "" else l
|
||||||
plusLineAndMaybeColonColumnOrEnd l mc
|
|
||||||
| l >= 0 = "+" ++ show l ++ maybe "" ((":"++).show) mc
|
return $ unwords $ cmd:args
|
||||||
| otherwise = ""
|
|
||||||
-- otherwise = "-f end-of-buffer"
|
|
||||||
-- XXX Problems with this:
|
|
||||||
-- it must appear after the filename, whereas +LINE:COL must appear before
|
|
||||||
-- it works only with emacs, not emacsclient
|
|
||||||
return $ unwords [editcmd, positionarg, f']
|
|
||||||
|
|
||||||
-- | Get the user's preferred edit command. This is the value of the
|
-- | Get the user's preferred edit command. This is the value of the
|
||||||
-- $HLEDGER_UI_EDITOR environment variable, or of $EDITOR, or a
|
-- $HLEDGER_UI_EDITOR environment variable, or of $EDITOR, or a
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user