ui: txn: up/down steps through txns in the account
This commit is contained in:
		
							parent
							
								
									2feace32dd
								
							
						
					
					
						commit
						4691454908
					
				| @ -2288,6 +2288,10 @@ will display the transaction in full, as a general journal entry | ||||
| This shows more detail, such as the cleared status, transaction code, | ||||
| comments and tags, and the individual account postings. | ||||
| 
 | ||||
| You can use the cursor up/down keys to step through all transactions | ||||
| listed in the previous account register screen. Cursor left returns to | ||||
| that screen. | ||||
| 
 | ||||
| ##### Error screen | ||||
| 
 | ||||
| This screen will appear if there is a problem, such as a parse error, | ||||
|  | ||||
| @ -209,7 +209,13 @@ handleRegisterScreen st@AppState{ | ||||
| 
 | ||||
|     Vty.EvKey (k) [] | k `elem` [Vty.KRight, Vty.KEnter] -> do | ||||
|       case listSelectedElement l of | ||||
|         Just (_, (_, _, _, _, _, t)) -> continue $ screenEnter d TS.screen{tsState=t} st | ||||
|         Just (_, (_, _, _, _, _, t)) -> | ||||
|           let | ||||
|             ts = map sixth6 $ V.toList $ listElements l | ||||
|             numberedts = zip [1..] ts | ||||
|             i = fromIntegral $ maybe 0 (+1) $ elemIndex t ts -- XXX | ||||
|           in | ||||
|             continue $ screenEnter d TS.screen{tsState=((i,t),numberedts,acct)} st | ||||
|         Nothing -> continue st | ||||
| 
 | ||||
|     -- fall through to the list's event handler (handles [pg]up/down) | ||||
|  | ||||
| @ -1,6 +1,6 @@ | ||||
| -- The transaction screen, showing a single transaction's general journal entry. | ||||
| 
 | ||||
| {-# LANGUAGE OverloadedStrings #-} -- , FlexibleContexts | ||||
| {-# LANGUAGE OverloadedStrings, TupleSections #-} -- , FlexibleContexts | ||||
| 
 | ||||
| module Hledger.UI.TransactionScreen | ||||
|  (screen | ||||
| @ -11,11 +11,13 @@ where | ||||
| import Control.Monad.IO.Class (liftIO) | ||||
| -- import Data.List | ||||
| -- import Data.List.Split (splitOn) | ||||
| -- import Data.Ord | ||||
| import Data.Monoid | ||||
| -- import Data.Maybe | ||||
| import Data.Time.Calendar (Day) | ||||
| -- import qualified Data.Vector as V | ||||
| import Graphics.Vty as Vty | ||||
| -- import Safe (headDef, lastDef) | ||||
| import Brick | ||||
| -- import Brick.Widgets.List | ||||
| -- import Brick.Widgets.Border | ||||
| @ -32,25 +34,29 @@ import Hledger.UI.UIUtils | ||||
| import qualified Hledger.UI.ErrorScreen as ES (screen) | ||||
| 
 | ||||
| screen = TransactionScreen{ | ||||
|    tsState   = nulltransaction | ||||
|    tsState   = ((1,nulltransaction),[(1,nulltransaction)],"") | ||||
|   ,sInitFn   = initTransactionScreen | ||||
|   ,sDrawFn   = drawTransactionScreen | ||||
|   ,sHandleFn = handleTransactionScreen | ||||
|   } | ||||
| 
 | ||||
| initTransactionScreen :: Day -> AppState -> AppState | ||||
| initTransactionScreen _d st@AppState{aopts=_opts, ajournal=_j, aScreen=_s@TransactionScreen{tsState=_t}} = st | ||||
| initTransactionScreen _d st@AppState{aopts=_opts, ajournal=_j, aScreen=_s@TransactionScreen{tsState=_}} = st | ||||
| initTransactionScreen _ _ = error "init function called with wrong screen type, should not happen" | ||||
| 
 | ||||
| drawTransactionScreen :: AppState -> [Widget] | ||||
| drawTransactionScreen AppState{ -- aopts=_uopts@UIOpts{cliopts_=_copts@CliOpts{reportopts_=_ropts@ReportOpts{query_=querystr}}}, | ||||
|                                aScreen=TransactionScreen{tsState=t}} = [ui] | ||||
|                                aScreen=TransactionScreen{tsState=((i,t),nts,acct)}} = [ui] | ||||
|   where | ||||
|     -- datedesc = show (tdate t) ++ " " ++ tdescription t | ||||
|     toplabel = | ||||
|       str "Transaction " | ||||
|       <+> withAttr ("border" <> "bold") (str $ show (tdate t) ++ " " ++ tdescription t) | ||||
|       -- <+> withAttr ("border" <> "bold") (str $  | ||||
|       <+> withAttr ("border" <> "bold") (str $ show i) | ||||
|       <+> str (" of "++show (length nts)++" in "++acct) | ||||
|     bottomlabel = borderKeysStr [ | ||||
|        ("left", "return to register") | ||||
|       ,("up/down", "prev/next transaction") | ||||
|       ,("g", "reload") | ||||
|       ,("q", "quit") | ||||
|       ] | ||||
| @ -61,10 +67,14 @@ drawTransactionScreen _ = error "draw function called with wrong screen type, sh | ||||
| 
 | ||||
| handleTransactionScreen :: AppState -> Vty.Event -> EventM (Next AppState) | ||||
| handleTransactionScreen st@AppState{ | ||||
|    aScreen=_s@TransactionScreen{tsState=_t} | ||||
|    aScreen=s@TransactionScreen{tsState=((i,t),nts,acct)} | ||||
|   ,aopts=UIOpts{cliopts_=_copts} | ||||
|   ,ajournal=j | ||||
|   } e = do | ||||
|   d <- liftIO getCurrentDay | ||||
|   let | ||||
|     (iprev,tprev) = maybe (i,t) ((i-1),) $ lookup (i-1) nts | ||||
|     (inext,tnext) = maybe (i,t) ((i+1),) $ lookup (i+1) nts | ||||
|   case e of | ||||
|     Vty.EvKey Vty.KEsc []        -> halt st | ||||
|     Vty.EvKey (Vty.KChar 'q') [] -> halt st | ||||
| @ -76,6 +86,9 @@ handleTransactionScreen st@AppState{ | ||||
|         Right j' -> continue $ reload j' d st | ||||
|         Left err -> continue $ screenEnter d ES.screen{esState=err} st | ||||
| 
 | ||||
|     Vty.EvKey (Vty.KUp) []       -> continue $ reload j d st{aScreen=s{tsState=((iprev,tprev),nts,acct)}} | ||||
|     Vty.EvKey (Vty.KDown) []     -> continue $ reload j d st{aScreen=s{tsState=((inext,tnext),nts,acct)}} | ||||
| 
 | ||||
|     Vty.EvKey (Vty.KLeft) []     -> continue $ popScreen st | ||||
| 
 | ||||
|     _ev -> continue st | ||||
|  | ||||
| @ -41,7 +41,7 @@ data Screen = | ||||
|     ,sDrawFn :: AppState -> [Widget] | ||||
|     } | ||||
|   | TransactionScreen { | ||||
|      tsState :: Transaction                                       -- ^ the transaction we are viewing | ||||
|      tsState :: ((Integer,Transaction), [(Integer,Transaction)], AccountName)         -- ^ the (numbered) transaction we are viewing, a numbered list of transactions we can step through, and the account whose register we entered this screen from | ||||
|     ,sInitFn :: Day -> AppState -> AppState | ||||
|     ,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) | ||||
|     ,sDrawFn :: AppState -> [Widget] | ||||
|  | ||||
| @ -175,6 +175,10 @@ will display the transaction in full, as a general journal entry | ||||
| This shows more detail, such as the cleared status, transaction code, | ||||
| comments and tags, and the individual account postings. | ||||
| 
 | ||||
| You can use the cursor up/down keys to step through all transactions | ||||
| listed in the previous account register screen. Cursor left returns to | ||||
| that screen. | ||||
| 
 | ||||
| ## Error screen | ||||
| 
 | ||||
| This screen will appear if there is a problem, such as a parse error, | ||||
| @ -201,7 +205,7 @@ The need to precede options with `--` when invoked from hledger is awkward. | ||||
| 
 | ||||
| `-f-` doesn't work (hledger-ui can't read from stdin). | ||||
| 
 | ||||
| `-V` doesn't affect the register screen. | ||||
| `-V` affects only the accounts screen. | ||||
| 
 | ||||
| When you press `g`, the current and all previous screens are | ||||
| regenerated, which may cause a noticeable pause. Also there is no | ||||
| @ -210,3 +214,7 @@ visual indication that this is in progress. | ||||
| The register screen's switching between historic balance and running | ||||
| total based on query arguments may be confusing, and there is no | ||||
| column heading to indicate which is being displayed. | ||||
| 
 | ||||
| When you navigate to an earlier or later transaction with cursor | ||||
| up/down in the transaction screen, and then return to the register | ||||
| screen, the selection will not have moved. | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user