lib!: lib,web: Remove unused TransactionReport. Move the useful utility
functions to AccountTransactionsReport. If you use transactionsReport, you should either use entryReport if you don't require a running total, or using accountTransactionsReport with thisacctq as Any or None (depending on what you want included in the running total).
This commit is contained in:
		
							parent
							
								
									acfbd36fb8
								
							
						
					
					
						commit
						f673e7c2eb
					
				| @ -15,7 +15,6 @@ module Hledger.Reports ( | ||||
|   module Hledger.Reports.ReportTypes, | ||||
|   module Hledger.Reports.EntriesReport, | ||||
|   module Hledger.Reports.PostingsReport, | ||||
|   module Hledger.Reports.TransactionsReport, | ||||
|   module Hledger.Reports.AccountTransactionsReport, | ||||
|   module Hledger.Reports.BalanceReport, | ||||
|   module Hledger.Reports.MultiBalanceReport, | ||||
| @ -30,7 +29,6 @@ import Hledger.Reports.ReportTypes | ||||
| import Hledger.Reports.AccountTransactionsReport | ||||
| import Hledger.Reports.EntriesReport | ||||
| import Hledger.Reports.PostingsReport | ||||
| import Hledger.Reports.TransactionsReport | ||||
| import Hledger.Reports.BalanceReport | ||||
| import Hledger.Reports.MultiBalanceReport | ||||
| import Hledger.Reports.BudgetReport | ||||
|  | ||||
| @ -12,11 +12,19 @@ module Hledger.Reports.AccountTransactionsReport ( | ||||
|   accountTransactionsReport, | ||||
|   accountTransactionsReportItems, | ||||
|   transactionRegisterDate, | ||||
|   triOrigTransaction, | ||||
|   triDate, | ||||
|   triAmount, | ||||
|   triBalance, | ||||
|   triCommodityAmount, | ||||
|   triCommodityBalance, | ||||
|   accountTransactionsReportByCommodity, | ||||
|   tests_AccountTransactionsReport | ||||
| ) | ||||
| where | ||||
| 
 | ||||
| import Data.List (mapAccumL, nub, partition, sortBy) | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Ord (comparing) | ||||
| import Data.Maybe (catMaybes) | ||||
| import Data.Text (Text) | ||||
| @ -78,6 +86,13 @@ type AccountTransactionsReportItem = | ||||
|   ,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction | ||||
|   ) | ||||
| 
 | ||||
| triOrigTransaction (torig,_,_,_,_,_) = torig | ||||
| triDate (_,tacct,_,_,_,_) = tdate tacct | ||||
| triAmount (_,_,_,_,a,_) = a | ||||
| triBalance (_,_,_,_,_,a) = a | ||||
| triCommodityAmount c = filterMixedAmountByCommodity c  . triAmount | ||||
| triCommodityBalance c = filterMixedAmountByCommodity c  . triBalance | ||||
| 
 | ||||
| accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport | ||||
| accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = items | ||||
|   where | ||||
| @ -139,8 +154,7 @@ pshowTransactions = pshow . map (\t -> unwords [show $ tdate t, T.unpack $ tdesc | ||||
| -- | Generate transactions report items from a list of transactions, | ||||
| -- using the provided user-specified report query, a query specifying | ||||
| -- which account to use as the focus, a starting balance, a sign-setting | ||||
| -- function and a balance-summing function. Or with a None current account | ||||
| -- query, this can also be used for the transactionsReport. | ||||
| -- function and a balance-summing function. | ||||
| accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [AccountTransactionsReportItem] | ||||
| accountTransactionsReportItems reportq thisacctq bal signfn = | ||||
|     catMaybes . snd . | ||||
| @ -148,7 +162,6 @@ accountTransactionsReportItems reportq thisacctq bal signfn = | ||||
| 
 | ||||
| accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount -> Transaction -> (MixedAmount, Maybe AccountTransactionsReportItem) | ||||
| accountTransactionsReportItem reportq thisacctq signfn bal torig = balItem | ||||
|     -- 201403: This is used for both accountTransactionsReport and transactionsReport, 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 | ||||
| @ -201,6 +214,39 @@ summarisePostingAccounts ps = | ||||
|     displayps | null realps = ps | ||||
|               | otherwise   = realps | ||||
| 
 | ||||
| -- | Split an  account transactions report whose items may involve several commodities, | ||||
| -- into one or more single-commodity account transactions reports. | ||||
| accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)] | ||||
| accountTransactionsReportByCommodity tr = | ||||
|   [(c, filterAccountTransactionsReportByCommodity c tr) | c <- commodities tr] | ||||
|   where | ||||
|     commodities = nubSort . map acommodity . concatMap (amounts . triAmount) | ||||
| 
 | ||||
| -- | Remove account transaction report items and item amount (and running | ||||
| -- balance amount) components that don't involve the specified | ||||
| -- commodity. Other item fields such as the transaction are left unchanged. | ||||
| filterAccountTransactionsReportByCommodity :: CommoditySymbol -> AccountTransactionsReport -> AccountTransactionsReport | ||||
| filterAccountTransactionsReportByCommodity c = | ||||
|     fixTransactionsReportItemBalances . concatMap (filterTransactionsReportItemByCommodity c) | ||||
|   where | ||||
|     filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal) | ||||
|       | c `elem` cs = [item'] | ||||
|       | otherwise   = [] | ||||
|       where | ||||
|         cs = map acommodity $ amounts a | ||||
|         item' = (t,t2,s,o,a',bal) | ||||
|         a' = filterMixedAmountByCommodity c a | ||||
| 
 | ||||
|     fixTransactionsReportItemBalances [] = [] | ||||
|     fixTransactionsReportItemBalances [i] = [i] | ||||
|     fixTransactionsReportItemBalances items = reverse $ i:(go startbal is) | ||||
|       where | ||||
|         i:is = reverse items | ||||
|         startbal = filterMixedAmountByCommodity c $ triBalance i | ||||
|         go _ [] = [] | ||||
|         go bal ((t,t2,s,o,amt,_):is) = (t,t2,s,o,amt,bal'):go bal' is | ||||
|           where bal' = bal `maPlus` amt | ||||
| 
 | ||||
| -- tests | ||||
| 
 | ||||
| tests_AccountTransactionsReport = tests "AccountTransactionsReport" [ | ||||
|  | ||||
| @ -1,108 +0,0 @@ | ||||
| {-# LANGUAGE FlexibleInstances #-} | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-| | ||||
| 
 | ||||
| A transactions report. Like an EntriesReport, but with more | ||||
| information such as a running balance. | ||||
| 
 | ||||
| -} | ||||
| 
 | ||||
| module Hledger.Reports.TransactionsReport ( | ||||
|   TransactionsReport, | ||||
|   TransactionsReportItem, | ||||
|   transactionsReport, | ||||
|   transactionsReportByCommodity, | ||||
|   triOrigTransaction, | ||||
|   triDate, | ||||
|   triAmount, | ||||
|   triBalance, | ||||
|   triCommodityAmount, | ||||
|   triCommodityBalance, | ||||
|   tests_TransactionsReport | ||||
| ) | ||||
| where | ||||
| 
 | ||||
| import Data.List (sortBy) | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Ord (comparing) | ||||
| import Data.Text (Text) | ||||
| 
 | ||||
| import Hledger.Data | ||||
| import Hledger.Query | ||||
| import Hledger.Reports.ReportOptions | ||||
| import Hledger.Reports.AccountTransactionsReport | ||||
| import Hledger.Utils | ||||
| 
 | ||||
| 
 | ||||
| -- | A transactions report includes a list of transactions touching multiple accounts | ||||
| -- (posting-filtered and unfiltered variants), a running balance, and some | ||||
| -- other information helpful for rendering a register view with or without a notion | ||||
| -- of current account(s). Two kinds of report use this data structure, see transactionsReport | ||||
| -- and accountTransactionsReport below for details. | ||||
| type TransactionsReport = [TransactionsReportItem] -- line items, one per transaction | ||||
| type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified | ||||
|                               ,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 | ||||
|                               ,Text        -- a display string describing the other account(s), if any | ||||
|                               ,MixedAmount -- the amount posted to the current account(s) by the filtered postings (or total amount posted) | ||||
|                               ,MixedAmount -- the running total of item amounts, starting from zero; | ||||
|                                            -- or with --historical, the running total including items | ||||
|                                            -- (matched by the report query) preceding the report period | ||||
|                               ) | ||||
| 
 | ||||
| triOrigTransaction (torig,_,_,_,_,_) = torig | ||||
| triDate (_,tacct,_,_,_,_) = tdate tacct | ||||
| triAmount (_,_,_,_,a,_) = a | ||||
| triBalance (_,_,_,_,_,a) = a | ||||
| triCommodityAmount c = filterMixedAmountByCommodity c  . triAmount | ||||
| triCommodityBalance c = filterMixedAmountByCommodity c  . triBalance | ||||
| 
 | ||||
| -- | Select transactions from the whole journal. This is similar to a | ||||
| -- "postingsReport" except with transaction-based report items which | ||||
| -- are ordered most recent first. XXX Or an EntriesReport - use that instead ? | ||||
| -- This is used by hledger-web's journal view. | ||||
| transactionsReport :: ReportSpec -> Journal -> Query -> TransactionsReport | ||||
| transactionsReport rspec j q = items | ||||
|    where | ||||
|      -- XXX items' first element should be the full transaction with all postings | ||||
|      items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts | ||||
|      ts    = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j | ||||
|      date = transactionDateFn $ rsOpts rspec | ||||
| 
 | ||||
| -- | Split a transactions report whose items may involve several commodities, | ||||
| -- into one or more single-commodity transactions reports. | ||||
| transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)] | ||||
| transactionsReportByCommodity tr = | ||||
|   [(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr] | ||||
|   where | ||||
|     transactionsReportCommodities = nubSort . map acommodity . concatMap (amounts . triAmount) | ||||
| 
 | ||||
| -- Remove transaction report items and item amount (and running | ||||
| -- balance amount) components that don't involve the specified | ||||
| -- commodity. Other item fields such as the transaction are left unchanged. | ||||
| filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport | ||||
| filterTransactionsReportByCommodity c = | ||||
|     fixTransactionsReportItemBalances . concatMap (filterTransactionsReportItemByCommodity c) | ||||
|   where | ||||
|     filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal) | ||||
|       | c `elem` cs = [item'] | ||||
|       | otherwise   = [] | ||||
|       where | ||||
|         cs = map acommodity $ amounts a | ||||
|         item' = (t,t2,s,o,a',bal) | ||||
|         a' = filterMixedAmountByCommodity c a | ||||
| 
 | ||||
|     fixTransactionsReportItemBalances [] = [] | ||||
|     fixTransactionsReportItemBalances [i] = [i] | ||||
|     fixTransactionsReportItemBalances items = reverse $ i:(go startbal is) | ||||
|       where | ||||
|         i:is = reverse items | ||||
|         startbal = filterMixedAmountByCommodity c $ triBalance i | ||||
|         go _ [] = [] | ||||
|         go bal ((t,t2,s,o,amt,_):is) = (t,t2,s,o,amt,bal'):go bal' is | ||||
|           where bal' = bal `maPlus` amt | ||||
| 
 | ||||
| -- tests | ||||
| 
 | ||||
| tests_TransactionsReport = tests "TransactionsReport" [ | ||||
|  ] | ||||
| @ -76,7 +76,6 @@ library | ||||
|       Hledger.Reports.EntriesReport | ||||
|       Hledger.Reports.MultiBalanceReport | ||||
|       Hledger.Reports.PostingsReport | ||||
|       Hledger.Reports.TransactionsReport | ||||
|       Hledger.Utils | ||||
|       Hledger.Utils.Color | ||||
|       Hledger.Utils.Debug | ||||
|  | ||||
| @ -127,7 +127,6 @@ library: | ||||
|   - Hledger.Reports.EntriesReport | ||||
|   - Hledger.Reports.MultiBalanceReport | ||||
|   - Hledger.Reports.PostingsReport | ||||
|   - Hledger.Reports.TransactionsReport | ||||
|   - Hledger.Utils | ||||
|   - Hledger.Utils.Color | ||||
|   - Hledger.Utils.Debug | ||||
|  | ||||
| @ -98,8 +98,8 @@ decorateLinks = | ||||
|             map ((,) (Just acct)) name ++ map ((,) Nothing) comma) | ||||
| 
 | ||||
| -- | Generate javascript/html for a register balance line chart based on | ||||
| -- the provided "TransactionsReportItem"s. | ||||
| registerChartHtml :: Text -> String -> [(CommoditySymbol, [TransactionsReportItem])] -> HtmlUrl AppRoute | ||||
| -- the provided "AccountTransactionsReportItem"s. | ||||
| registerChartHtml :: Text -> String -> [(CommoditySymbol, [AccountTransactionsReportItem])] -> HtmlUrl AppRoute | ||||
| registerChartHtml q title percommoditytxnreports = $(hamletFile "templates/chart.hamlet") | ||||
|  -- have to make sure plot is not called when our container (maincontent) | ||||
|  -- is hidden, eg with add form toggled | ||||
|  | ||||
| @ -2,7 +2,7 @@ | ||||
|   #{header} | ||||
| 
 | ||||
| <div .hidden-xs> | ||||
|   ^{registerChartHtml q balancelabel $ transactionsReportByCommodity items} | ||||
|   ^{registerChartHtml q balancelabel $ accountTransactionsReportByCommodity items} | ||||
| 
 | ||||
| <div.table-responsive> | ||||
|   <table .table.table-striped.table-condensed> | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user