;ui: E key: simplify; drop buggy emacs end-of-file positioning
This commit is contained in:
		
							parent
							
								
									67635106d2
								
							
						
					
					
						commit
						44da1e1cb7
					
				| @ -310,7 +310,7 @@ asHandle ui0@UIState{ | ||||
|         VtyEvent (EvKey (KChar 'I') []) -> continue $ uiCheckBalanceAssertions d (toggleIgnoreBalanceAssertions ui) | ||||
|         VtyEvent (EvKey (KChar 'a') []) -> suspendAndResume $ clearScreen >> setCursorPosition 0 0 >> add copts j >> uiReloadJournalIfChanged copts d j ui | ||||
|         VtyEvent (EvKey (KChar 'A') []) -> suspendAndResume $ void (runIadd (journalFilePath j)) >> uiReloadJournalIfChanged copts d j ui | ||||
|         VtyEvent (EvKey (KChar 'E') []) -> suspendAndResume $ void (runEditor endPos (journalFilePath j)) >> uiReloadJournalIfChanged copts d j ui | ||||
|         VtyEvent (EvKey (KChar 'E') []) -> suspendAndResume $ void (runEditor endPosition (journalFilePath j)) >> uiReloadJournalIfChanged copts d j ui | ||||
|         VtyEvent (EvKey (KChar 'B') []) -> continue $ regenerateScreens j d $ toggleCost ui | ||||
|         VtyEvent (EvKey (KChar 'V') []) -> continue $ regenerateScreens j d $ toggleValue ui | ||||
|         VtyEvent (EvKey (KChar '0') []) -> continue $ regenerateScreens j d $ setDepth (Just 0) ui | ||||
|  | ||||
| @ -2,11 +2,15 @@ | ||||
| 
 | ||||
| -- {-# LANGUAGE OverloadedStrings #-} | ||||
| 
 | ||||
| module Hledger.UI.Editor | ||||
| module Hledger.UI.Editor ( | ||||
|    -- TextPosition | ||||
|    endPosition | ||||
|   ,runEditor | ||||
|   ,runIadd | ||||
|   ) | ||||
| where | ||||
| 
 | ||||
| import Control.Applicative ((<|>)) | ||||
| import Data.List | ||||
| import Safe | ||||
| import System.Environment | ||||
| import System.Exit | ||||
| @ -16,66 +20,43 @@ import System.Process | ||||
| import Hledger | ||||
| 
 | ||||
| -- | A position we can move to in a text editor: a line and optional column number. | ||||
| -- 1 (or 0) means the first and -1 means the last (and -2 means the second last, etc. | ||||
| -- though this may not be well supported.) | ||||
| -- Line number 1 or 0 means the first line. A negative line number means the last line. | ||||
| type TextPosition = (Int, Maybe Int) | ||||
| 
 | ||||
| endPos :: Maybe TextPosition | ||||
| endPos = Just (-1,Nothing) | ||||
| -- | The text position meaning "last line, first column". | ||||
| endPosition :: Maybe TextPosition | ||||
| endPosition = Just (-1,Nothing) | ||||
| 
 | ||||
| -- | Run the hledger-iadd executable (an alternative to the built-in add command), | ||||
| -- or raise an error. | ||||
| -- | Run the hledger-iadd executable on the given file, blocking until it exits, | ||||
| -- and return the exit code; or raise an error. | ||||
| -- hledger-iadd is an alternative to the built-in add command. | ||||
| runIadd :: FilePath -> IO ExitCode | ||||
| runIadd f = runCommand ("hledger-iadd -f " ++ f) >>= waitForProcess | ||||
| 
 | ||||
| -- | Try running the user's preferred text editor, or a default edit command, | ||||
| -- on the main journal file, blocking until it exits, and returning the exit code; | ||||
| -- or raise an error. | ||||
| -- | Run the user's preferred text editor (or try a default editor), | ||||
| -- on the given file, blocking until it exits, and return the exit | ||||
| -- code; or raise an error. If a text position is provided, the editor | ||||
| -- will be focussed at that position in the file, if we know how. | ||||
| runEditor :: Maybe TextPosition -> FilePath -> IO ExitCode | ||||
| runEditor mpos f = editorOpenPositionCommand mpos f >>= runCommand >>= waitForProcess | ||||
| runEditor mpos f = editFileAtPositionCommand mpos f >>= runCommand >>= waitForProcess | ||||
| 
 | ||||
| -- Get the basic shell command to start the user's preferred text editor. | ||||
| -- This is the value of environment variable $HLEDGER_UI_EDITOR, or $EDITOR, or | ||||
| -- a default (emacsclient -a '' -nw, start/connect to an emacs daemon in terminal mode). | ||||
| editorCommand :: IO String | ||||
| editorCommand = do | ||||
|   hledger_ui_editor_env <- lookupEnv "HLEDGER_UI_EDITOR" | ||||
|   editor_env            <- lookupEnv "EDITOR" | ||||
|   let Just cmd = | ||||
|         hledger_ui_editor_env | ||||
|         <|> editor_env | ||||
|         <|> Just "emacsclient -a '' -nw" | ||||
|   return cmd | ||||
| 
 | ||||
| -- | Editors which we know how to open at a specific file position, | ||||
| -- and Other for the rest. | ||||
| data EditorType = Emacs | EmacsClient | Vi | Nano | Other | ||||
| 
 | ||||
| -- Identify which text editor is being used in the basic editor command, if possible. | ||||
| identifyEditor :: String -> EditorType | ||||
| identifyEditor cmd | ||||
|   | "emacsclient" `isPrefixOf` exe = EmacsClient | ||||
|   | "emacs" `isPrefixOf` exe       = Emacs | ||||
|   | exe `elem` ["vi","nvim","vim","ex","view","gvim","gview","evim","eview","rvim","rview","rgvim","rgview"] | ||||
|                                    = Vi | ||||
|   | "nano" `isPrefixOf` exe        = Nano | ||||
|   | otherwise                      = Other | ||||
|   where | ||||
|     exe = lowercase $ takeFileName $ headDef "" $ words' cmd | ||||
| 
 | ||||
| -- | Get a shell command to start the user's preferred text editor, or a default, | ||||
| -- and optionally jump to a given position in the given file. This will be the basic | ||||
| -- editor command, with the appropriate options added, if we know how. | ||||
| -- Currently we know how to do this for emacs, vi and nano. | ||||
| -- | 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 | ||||
| -- 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 last line for: vi. | ||||
| -- | ||||
| -- Some tests: With line and column numbers specified, | ||||
| -- @ | ||||
| -- Some tests: | ||||
| -- When EDITOR is:  The command should be: | ||||
| -- ---------------  ----------------------------------- | ||||
| -- notepad          notepad FILE | ||||
| -- vi               vi +LINE FILE | ||||
| -- emacs            emacs +LINE:COL FILE | ||||
| -- (unset)          emacs -nw FILE -f end-of-buffer | ||||
| -- if EDITOR is:  the command should be: | ||||
| -- -------------  ----------------------------------- | ||||
| -- notepad        notepad FILE | ||||
| -- vi             vi +LINE FILE | ||||
| --                vi + FILE                                    # negative LINE | ||||
| -- emacs          emacs +LINE:COL FILE | ||||
| --                emacs FILE                                   # negative LINE | ||||
| -- (unset)        emacsclient -a '' -nw +LINE:COL FILE | ||||
| --                emacsclient -a '' -nw FILE                   # negative LINE | ||||
| -- @ | ||||
| -- | ||||
| -- How to open editors at the last line of a file: | ||||
| @ -84,20 +65,44 @@ identifyEditor cmd | ||||
| -- vi:     vi + FILE | ||||
| -- @ | ||||
| -- | ||||
| editorOpenPositionCommand :: Maybe TextPosition -> FilePath -> IO String | ||||
| editorOpenPositionCommand mpos f = do | ||||
|   cmd <- editorCommand | ||||
|   return $ cmd ++ " " ++  | ||||
|    case (identifyEditor cmd, mpos) of | ||||
|     (EmacsClient , Just (l,mc)) | l >= 0 -> emacsposopt l mc ++ " " ++ f' | ||||
|     (EmacsClient , Just (l,mc)) | l <  0 -> emacsposopt 999999999 mc ++ " " ++ f' | ||||
|     (Emacs       , Just (l,mc)) | l >= 0 -> emacsposopt l mc ++ " " ++ f' | ||||
|     (Emacs       , Just (l,_))  | l <  0 -> f' ++ " -f end-of-buffer" | ||||
|     (Vi          , Just (l,_))           -> viposopt l ++ " " ++ f' | ||||
|     (Nano        , Just (l,_))           -> nanoposopt l ++ " " ++ f' | ||||
|     _                                    -> f' | ||||
|     where | ||||
|       f' = singleQuoteIfNeeded f | ||||
|       emacsposopt l mc = "+" ++ show l ++ maybe "" ((":"++).show) mc | ||||
|       viposopt l       = "+" ++ if l >= 0 then show l else "" | ||||
|       nanoposopt l mc  = "+" ++ show l ++ maybe "" ((","++).show) mc | ||||
| editFileAtPositionCommand :: Maybe TextPosition -> FilePath -> IO String | ||||
| editFileAtPositionCommand mpos f = do | ||||
|   let f' = singleQuoteIfNeeded f | ||||
|   editcmd <- getEditCommand | ||||
|   let editor = lowercase $ takeFileName $ headDef "" $ words' editcmd | ||||
|   let positionarg = | ||||
|         case mpos of | ||||
|           Just (l, mc) | ||||
|             | editor `elem` [ | ||||
|                 "ex", | ||||
|                 "vi","vim","view","nvim","evim","eview", | ||||
|                 "gvim","gview","rvim","rview","rgvim","rgview" | ||||
|                 ] -> plusAndMaybeLine l mc | ||||
|           Just (l, mc) | ||||
|             | editor `elem` ["emacs", "emacsclient"] -> plusLineAndMaybeColonColumnOrEnd l mc | ||||
|           Just (l, mc) | ||||
|             | editor `elem` ["nano"] -> plusLineAndMaybeCommaColumn l mc | ||||
|           _ -> "" | ||||
|         where | ||||
|           plusAndMaybeLine            l _  = "+" ++ if l >= 0 then show l else "" | ||||
|           plusLineAndMaybeCommaColumn l mc = "+" ++ show l ++ maybe "" ((","++).show) mc | ||||
|           plusLineAndMaybeColonColumnOrEnd l mc | ||||
|             | l >= 0    = "+" ++ show l ++ maybe "" ((":"++).show) mc | ||||
|             | 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 | ||||
| -- $HLEDGER_UI_EDITOR environment variable, or of $EDITOR, or a | ||||
| -- default ("emacsclient -a '' -nw", which starts/connects to an emacs | ||||
| -- daemon in terminal mode). | ||||
| getEditCommand :: IO String | ||||
| getEditCommand = do | ||||
|   hledger_ui_editor_env <- lookupEnv "HLEDGER_UI_EDITOR" | ||||
|   editor_env            <- lookupEnv "EDITOR" | ||||
|   let Just cmd = hledger_ui_editor_env <|> editor_env <|> Just "emacsclient -a '' -nw" | ||||
|   return cmd | ||||
| 
 | ||||
|  | ||||
| @ -99,7 +99,7 @@ esHandle ui@UIState{aScreen=ErrorScreen{..} | ||||
|           where | ||||
|             (pos,f) = case parsewithString hledgerparseerrorpositionp esError of | ||||
|                         Right (f,l,c) -> (Just (l, Just c),f) | ||||
|                         Left  _       -> (endPos, journalFilePath j) | ||||
|                         Left  _       -> (endPosition, journalFilePath j) | ||||
|         e | e `elem` [VtyEvent (EvKey (KChar 'g') []), AppEvent FileChange] -> | ||||
|           liftIO (uiReloadJournal copts d (popScreen ui)) >>= continue . uiCheckBalanceAssertions d | ||||
| --           (ej, _) <- liftIO $ journalReloadIfChanged copts d j | ||||
|  | ||||
| @ -315,7 +315,7 @@ rsHandle ui@UIState{ | ||||
|         VtyEvent (EvKey (KChar 'E') []) -> suspendAndResume $ void (runEditor pos f) >> uiReloadJournalIfChanged copts d j ui | ||||
|           where | ||||
|             (pos,f) = case listSelectedElement rsList of | ||||
|                         Nothing -> (endPos, journalFilePath j) | ||||
|                         Nothing -> (endPosition, journalFilePath j) | ||||
|                         Just (_, RegisterScreenItem{ | ||||
|                           rsItemTransaction=Transaction{tsourcepos=GenericSourcePos f l c}}) -> (Just (l, Just c),f) | ||||
|                         Just (_, RegisterScreenItem{ | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user