ui: transaction: ignore real/cleared/empty, always show full txn (#354)
This commit clarifies the account transactions report: as before the included transactions
are the original unfiltered transactions, but now the change and running balance amounts
are calculated from the report-matched postings. This fixed the limitation noted in 509f558,
so that toggling real mode in any screen could work. Then I decided the transaction screen
shouldn't show a partial transaction after all, so real/cleared filtering is no longer allowed or indicated here.
			
			
This commit is contained in:
		
							parent
							
								
									7f3ae224e2
								
							
						
					
					
						commit
						7c8d7e9820
					
				@ -51,11 +51,11 @@ type TransactionsReport = (String                   -- label for the balance col
 | 
				
			|||||||
                          ,[TransactionsReportItem] -- line items, one per transaction
 | 
					                          ,[TransactionsReportItem] -- line items, one per transaction
 | 
				
			||||||
                          )
 | 
					                          )
 | 
				
			||||||
type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified
 | 
					type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified
 | 
				
			||||||
                              ,Transaction -- the transaction as seen from a particular account
 | 
					                              ,Transaction -- the transaction as seen from a particular account, with postings maybe filtered
 | 
				
			||||||
                              ,Bool        -- is this a split, ie more than one other account posting
 | 
					                              ,Bool        -- is this a split, ie more than one other account posting
 | 
				
			||||||
                              ,String      -- a display string describing the other account(s), if any
 | 
					                              ,String      -- a display string describing the other account(s), if any
 | 
				
			||||||
                              ,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
 | 
					                              ,MixedAmount -- the amount posted to the current account(s) by the filtered postings (or total amount posted)
 | 
				
			||||||
                              ,MixedAmount -- the running balance for the current account(s) after this transaction
 | 
					                              ,MixedAmount -- the running balance for the current account(s) after the above
 | 
				
			||||||
                              )
 | 
					                              )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
triOrigTransaction (torig,_,_,_,_,_) = torig
 | 
					triOrigTransaction (torig,_,_,_,_,_) = torig
 | 
				
			||||||
@ -115,21 +115,18 @@ type AccountTransactionsReportItem =
 | 
				
			|||||||
accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> AccountTransactionsReport
 | 
					accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> AccountTransactionsReport
 | 
				
			||||||
accountTransactionsReport opts j q thisacctquery = (label, items)
 | 
					accountTransactionsReport opts j q thisacctquery = (label, items)
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
     -- transactions with excluded currencies and excluded virtual postings removed
 | 
					    -- get all transactions, with amounts converted to cost basis if -B
 | 
				
			||||||
     ts1 = jtxns $
 | 
					    ts1 = jtxns $ journalSelectingAmountFromOpts opts j
 | 
				
			||||||
           (if queryIsNull realq then id else filterJournalPostings realq) $ -- apply Real filter if it's in q
 | 
					    -- apply any cur:SYM filters in q
 | 
				
			||||||
           (if queryIsNull symq  then id else filterJournalAmounts symq) $   -- apply any cur:SYM filters in q
 | 
					 | 
				
			||||||
           journalSelectingAmountFromOpts opts j  -- convert amounts to cost basis if -B
 | 
					 | 
				
			||||||
        where
 | 
					 | 
				
			||||||
          realq = filterQuery queryIsReal q
 | 
					 | 
				
			||||||
    symq  = filterQuery queryIsSym q
 | 
					    symq  = filterQuery queryIsSym q
 | 
				
			||||||
 | 
					    ts2 = (if queryIsNull symq then id else map (filterTransactionAmounts symq)) ts1
 | 
				
			||||||
     -- affecting this account
 | 
					    -- keep just the transactions affecting this account
 | 
				
			||||||
     ts2 = filter (matchesTransaction thisacctquery) ts1
 | 
					    ts3 = filter (matchesTransaction thisacctquery) ts2
 | 
				
			||||||
     -- with dates adjusted for account transactions report
 | 
					    -- adjust the transaction dates to the dates of postings to this account
 | 
				
			||||||
     ts3 = map (setTransactionDateToPostingDate q thisacctquery) ts2
 | 
					    -- XXX can be wrong since we filter real postings later ?
 | 
				
			||||||
     -- and sorted
 | 
					    ts4 = map (setTransactionDateToPostingDate q thisacctquery) ts3
 | 
				
			||||||
     ts = sortBy (comparing tdate) ts3
 | 
					    -- sort by the new dates
 | 
				
			||||||
 | 
					    ts = sortBy (comparing tdate) ts4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    -- starting balance: if we are filtering by a start date and nothing else,
 | 
					    -- starting balance: if we are filtering by a start date and nothing else,
 | 
				
			||||||
    -- the sum of postings to this account before that date; otherwise zero.
 | 
					    -- the sum of postings to this account before that date; otherwise zero.
 | 
				
			||||||
@ -168,34 +165,32 @@ totallabel = "Running Total"
 | 
				
			|||||||
balancelabel = "Historical Balance"
 | 
					balancelabel = "Historical Balance"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Generate transactions report items from a list of transactions,
 | 
					-- | Generate transactions report items from a list of transactions,
 | 
				
			||||||
-- using the provided query and current account queries, starting
 | 
					-- using the provided user-specified report query, a query specifying
 | 
				
			||||||
-- balance, sign-setting function and balance-summing function. With a
 | 
					-- which account to use as the focus, a starting balance, a sign-setting
 | 
				
			||||||
-- "this account" query of None, this can be used the for the
 | 
					-- function and a balance-summing function. Or with a None current account
 | 
				
			||||||
-- journalTransactionsReport also.
 | 
					-- query, this can also be used for the journalTransactionsReport.
 | 
				
			||||||
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [TransactionsReportItem]
 | 
					accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [TransactionsReportItem]
 | 
				
			||||||
accountTransactionsReportItems _ _ _ _ [] = []
 | 
					accountTransactionsReportItems _ _ _ _ [] = []
 | 
				
			||||||
accountTransactionsReportItems query thisacctquery bal signfn (torig:ts) =
 | 
					accountTransactionsReportItems reportq thisacctq bal signfn (torig:ts) =
 | 
				
			||||||
    -- This is used for both accountTransactionsReport and journalTransactionsReport,
 | 
					 | 
				
			||||||
    -- which makes it a bit overcomplicated
 | 
					 | 
				
			||||||
    case i of Just i' -> i':is
 | 
					    case i of Just i' -> i':is
 | 
				
			||||||
              Nothing -> is
 | 
					              Nothing -> is
 | 
				
			||||||
 | 
					    -- 201403: This is used for both accountTransactionsReport and journalTransactionsReport, which makes it a bit overcomplicated
 | 
				
			||||||
 | 
					    -- 201407: I've lost my grip on this, let's just hope for the best
 | 
				
			||||||
 | 
					    -- 201606: we now calculate change and balance from filtered postings, check this still works well for all callers XXX
 | 
				
			||||||
    where
 | 
					    where
 | 
				
			||||||
      -- XXX I've lost my grip on this, let's just hope for the best
 | 
					      tacct@Transaction{tpostings=reportps} = filterTransactionPostings reportq torig
 | 
				
			||||||
      origps = tpostings torig
 | 
					      (i,bal') = case reportps of
 | 
				
			||||||
      tacct@Transaction{tpostings=queryps} = filterTransactionPostings query torig
 | 
					           [] -> (Nothing,bal)  -- no matched postings in this transaction, skip it
 | 
				
			||||||
      (thisacctps, otheracctps) = partition (matchesPosting thisacctquery) origps
 | 
					 | 
				
			||||||
      amt = negate $ sum $ map pamount thisacctps
 | 
					 | 
				
			||||||
      numotheraccts = length $ nub $ map paccount otheracctps
 | 
					 | 
				
			||||||
      otheracctstr | thisacctquery == None = summarisePostingAccounts origps
 | 
					 | 
				
			||||||
                   | numotheraccts == 0    = summarisePostingAccounts thisacctps
 | 
					 | 
				
			||||||
                   | otherwise             = summarisePostingAccounts otheracctps
 | 
					 | 
				
			||||||
      (i,bal') = case queryps of
 | 
					 | 
				
			||||||
           [] -> (Nothing,bal)
 | 
					 | 
				
			||||||
           _  -> (Just (torig, tacct, numotheraccts > 1, otheracctstr, a, b), b)
 | 
					           _  -> (Just (torig, tacct, numotheraccts > 1, otheracctstr, a, b), b)
 | 
				
			||||||
                 where
 | 
					                 where
 | 
				
			||||||
                  a = signfn amt
 | 
					                  (thisacctps, otheracctps) = partition (matchesPosting thisacctq) reportps
 | 
				
			||||||
 | 
					                  numotheraccts = length $ nub $ map paccount otheracctps
 | 
				
			||||||
 | 
					                  otheracctstr | thisacctq == None  = summarisePostingAccounts reportps     -- no current account ? summarise all matched postings
 | 
				
			||||||
 | 
					                               | numotheraccts == 0 = summarisePostingAccounts thisacctps   -- only postings to current account ? summarise those
 | 
				
			||||||
 | 
					                               | otherwise          = summarisePostingAccounts otheracctps  -- summarise matched postings to other account(s)
 | 
				
			||||||
 | 
					                  a = signfn $ negate $ sum $ map pamount thisacctps
 | 
				
			||||||
                  b = bal + a
 | 
					                  b = bal + a
 | 
				
			||||||
      is = accountTransactionsReportItems query thisacctquery bal' signfn ts
 | 
					      is = accountTransactionsReportItems reportq thisacctq bal' signfn ts
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- -- | Generate a short readable summary of some postings, like
 | 
					-- -- | Generate a short readable summary of some postings, like
 | 
				
			||||||
-- -- "from (negatives) to (positives)".
 | 
					-- -- "from (negatives) to (positives)".
 | 
				
			||||||
 | 
				
			|||||||
@ -43,16 +43,10 @@ screen = TransactionScreen{
 | 
				
			|||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					
 | 
				
			||||||
initTransactionScreen :: Day -> AppState -> AppState
 | 
					initTransactionScreen :: Day -> AppState -> AppState
 | 
				
			||||||
initTransactionScreen d st@AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
 | 
					initTransactionScreen _d st@AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=_ropts}}
 | 
				
			||||||
                                    ,ajournal=_j
 | 
					                                    ,ajournal=_j
 | 
				
			||||||
                                    ,aScreen=s@TransactionScreen{tsState=((n,t),nts,a)}} =
 | 
					                                    ,aScreen=s@TransactionScreen{tsState=((n,t),nts,a)}} =
 | 
				
			||||||
  st{aScreen=s{tsState=((n, t'),nts,a)}}
 | 
					  st{aScreen=s{tsState=((n,t),nts,a)}}
 | 
				
			||||||
  where
 | 
					 | 
				
			||||||
    -- re-filter the postings, eg because real/virtual was toggled.
 | 
					 | 
				
			||||||
    -- get the original transaction from the list passed from the register screen.
 | 
					 | 
				
			||||||
    t' = case lookup n nts of
 | 
					 | 
				
			||||||
      Just torig -> filterTransactionPostings (queryFromOpts d ropts) torig
 | 
					 | 
				
			||||||
      Nothing    -> t -- shouldn't happen
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
initTransactionScreen _ _ = error "init function called with wrong screen type, should not happen"
 | 
					initTransactionScreen _ _ = error "init function called with wrong screen type, should not happen"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -69,23 +63,28 @@ drawTransactionScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
 | 
				
			|||||||
      <+> str " ("
 | 
					      <+> str " ("
 | 
				
			||||||
      <+> withAttr ("border" <> "bold") (str $ show i)
 | 
					      <+> withAttr ("border" <> "bold") (str $ show i)
 | 
				
			||||||
      <+> str (" of "++show (length nts)++" in "++T.unpack acct++")")
 | 
					      <+> str (" of "++show (length nts)++" in "++T.unpack acct++")")
 | 
				
			||||||
      <+> togglefilters
 | 
					-- on this screen we will ignore real/cleared/empty and always show all postings
 | 
				
			||||||
    togglefilters =
 | 
					--       <+> togglefilters
 | 
				
			||||||
      case concat [
 | 
					--     togglefilters =
 | 
				
			||||||
           if cleared_ ropts then ["cleared"] else []
 | 
					--       case concat [
 | 
				
			||||||
          ,if real_ ropts then ["real"] else []
 | 
					--            if cleared_ ropts then ["cleared"] else []
 | 
				
			||||||
          ] of
 | 
					--           ,if real_ ropts then ["real"] else []
 | 
				
			||||||
        [] -> str ""
 | 
					--           ] of
 | 
				
			||||||
        fs -> withAttr (borderAttr <> "query") (str $ " " ++ intercalate ", " fs) <+> str " postings"
 | 
					--         [] -> str ""
 | 
				
			||||||
 | 
					--         fs -> withAttr (borderAttr <> "query") (str $ " " ++ intercalate ", " fs) <+> str " postings"
 | 
				
			||||||
    bottomlabel = borderKeysStr [
 | 
					    bottomlabel = borderKeysStr [
 | 
				
			||||||
       ("left", "back")
 | 
					       ("left", "back")
 | 
				
			||||||
      ,("up/down", "prev/next")
 | 
					      ,("up/down", "prev/next")
 | 
				
			||||||
      ,("R", "real?")
 | 
					--       ,("C", "cleared?")
 | 
				
			||||||
 | 
					--       ,("R", "real?")
 | 
				
			||||||
      ,("g", "reload")
 | 
					      ,("g", "reload")
 | 
				
			||||||
      ,("q", "quit")
 | 
					      ,("q", "quit")
 | 
				
			||||||
      ]
 | 
					      ]
 | 
				
			||||||
    ui = Widget Greedy Greedy $ do
 | 
					    ui = Widget Greedy Greedy $ do
 | 
				
			||||||
      render $ defaultLayout toplabel bottomlabel $ str $ showTransactionUnelidedOneLineAmounts t
 | 
					      render $ defaultLayout toplabel bottomlabel $ str $
 | 
				
			||||||
 | 
					        showTransactionUnelidedOneLineAmounts $
 | 
				
			||||||
 | 
					        -- (if real_ ropts then filterTransactionPostings (Real True) else id) -- filter postings by --real
 | 
				
			||||||
 | 
					        t
 | 
				
			||||||
 | 
					
 | 
				
			||||||
drawTransactionScreen _ = error "draw function called with wrong screen type, should not happen"
 | 
					drawTransactionScreen _ = error "draw function called with wrong screen type, should not happen"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -132,10 +131,7 @@ handleTransactionScreen st@AppState{
 | 
				
			|||||||
        Left err -> continue $ screenEnter d ES.screen{esState=err} st
 | 
					        Left err -> continue $ screenEnter d ES.screen{esState=err} st
 | 
				
			||||||
 | 
					
 | 
				
			||||||
--     Vty.EvKey (Vty.KChar 'C') [] -> continue $ reload j d $ stToggleCleared st
 | 
					--     Vty.EvKey (Vty.KChar 'C') [] -> continue $ reload j d $ stToggleCleared st
 | 
				
			||||||
 | 
					--     Vty.EvKey (Vty.KChar 'R') [] -> continue $ reload j d $ stToggleReal st
 | 
				
			||||||
    Vty.EvKey (Vty.KChar 'R') [] ->
 | 
					 | 
				
			||||||
      -- just show/hide the real postings in this transaction, don't bother updating parent screens
 | 
					 | 
				
			||||||
      continue $ reload j d $ stToggleReal st
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
    Vty.EvKey (Vty.KUp) []       -> continue $ reload j d st{aScreen=s{tsState=((iprev,tprev),nts,acct)}}
 | 
					    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.KDown) []     -> continue $ reload j d st{aScreen=s{tsState=((inext,tnext),nts,acct)}}
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user