imp: bal: handle commodity-column flag in compound balance reports (#1654)
This commit is contained in:
		
							parent
							
								
									277227acf8
								
							
						
					
					
						commit
						710823e5d7
					
				| @ -231,10 +231,6 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ | |||||||
|                  Nothing             -> "") |                  Nothing             -> "") | ||||||
|            <> ":" |            <> ":" | ||||||
| 
 | 
 | ||||||
| -- | Add the second table below the first, discarding its column headings. |  | ||||||
| concatTables (Table hLeft hTop dat) (Table hLeft' _ dat') = |  | ||||||
|     Table (Tab.Group SingleLine [hLeft, hLeft']) hTop (dat ++ dat') |  | ||||||
| 
 |  | ||||||
| -- | Build a 'Table' from a multi-column balance report. | -- | Build a 'Table' from a multi-column balance report. | ||||||
| budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text WideBuilder | budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text WideBuilder | ||||||
| budgetReportAsTable | budgetReportAsTable | ||||||
| @ -263,7 +259,7 @@ budgetReportAsTable | |||||||
|       | no_total_ = id |       | no_total_ = id | ||||||
|       | otherwise = let rh = Tab.Group NoLine $ map Header (replicate (length totalrows) "") |       | otherwise = let rh = Tab.Group NoLine $ map Header (replicate (length totalrows) "") | ||||||
|                         ch = Header [] -- ignored |                         ch = Header [] -- ignored | ||||||
|                      in (`concatTables` Table rh ch totalrows) |                      in (flip (concatTables SingleLine) $ Table rh ch totalrows) | ||||||
| 
 | 
 | ||||||
|     maybetranspose |     maybetranspose | ||||||
|       | transpose_ = transpose |       | transpose_ = transpose | ||||||
|  | |||||||
| @ -21,6 +21,7 @@ module Text.Tabular.AsciiWide | |||||||
| , textCell | , textCell | ||||||
| , textsCell | , textsCell | ||||||
| , cellWidth | , cellWidth | ||||||
|  | , concatTables | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
| import Data.Maybe (fromMaybe) | import Data.Maybe (fromMaybe) | ||||||
| @ -295,3 +296,9 @@ lineart SingleLine SingleLine DoubleLine DoubleLine = pick "╪" "+" | |||||||
| lineart DoubleLine DoubleLine SingleLine SingleLine = pick "╫" "++" | lineart DoubleLine DoubleLine SingleLine SingleLine = pick "╫" "++" | ||||||
| 
 | 
 | ||||||
| lineart _          _          _          _          = const mempty | lineart _          _          _          _          = const mempty | ||||||
|  | 
 | ||||||
|  | 
 | ||||||
|  | -- | Add the second table below the first, discarding its column headings. | ||||||
|  | concatTables :: Properties -> Table rh ch a -> Table rh ch2 a -> Table rh ch a | ||||||
|  | concatTables prop (Table hLeft hTop dat) (Table hLeft' _ dat') = | ||||||
|  |     Table (Group prop [hLeft, hLeft']) hTop (dat ++ dat') | ||||||
|  | |||||||
| @ -246,18 +246,19 @@ module Hledger.Cli.Commands.Balance ( | |||||||
|  ,balanceReportAsText |  ,balanceReportAsText | ||||||
|  ,balanceReportAsCsv |  ,balanceReportAsCsv | ||||||
|  ,balanceReportItemAsText |  ,balanceReportItemAsText | ||||||
|  |  ,multiBalanceRowAsCsvText | ||||||
|  ,multiBalanceRowAsTableText |  ,multiBalanceRowAsTableText | ||||||
|  ,multiBalanceReportAsText |  ,multiBalanceReportAsText | ||||||
|  ,multiBalanceReportAsCsv |  ,multiBalanceReportAsCsv | ||||||
|  ,multiBalanceReportAsHtml |  ,multiBalanceReportAsHtml | ||||||
|  ,multiBalanceReportHtmlRows |  ,multiBalanceReportHtmlRows | ||||||
|  |  ,multiBalanceReportHtmlFootRow | ||||||
|  ,balanceReportAsTable |  ,balanceReportAsTable | ||||||
|  ,balanceReportTableAsText |  ,balanceReportTableAsText | ||||||
|  ,tests_Balance |  ,tests_Balance | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
| import Data.Default (def) | import Data.Default (def) | ||||||
| import Data.Function ((&)) |  | ||||||
| import Data.List (transpose, foldl', transpose) | import Data.List (transpose, foldl', transpose) | ||||||
| import qualified Data.Map as M | import qualified Data.Map as M | ||||||
| import qualified Data.Set as S | import qualified Data.Set as S | ||||||
| @ -672,9 +673,13 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_} | |||||||
|     (accts, rows) = unzip $ fmap fullRowAsTexts items |     (accts, rows) = unzip $ fmap fullRowAsTexts items | ||||||
|     renderacct row = |     renderacct row = | ||||||
|         T.replicate ((prrDepth row - 1) * 2) " " <> prrDisplayName row |         T.replicate ((prrDepth row - 1) * 2) " " <> prrDisplayName row | ||||||
|     addtotalrow | no_total_ opts = id |     addtotalrow | ||||||
|                 | otherwise      = \tab -> foldl (&) tab . zipWith ($) (flip (+----+) : repeat (flip (+.+))) $ totalrows |       | no_total_ opts = id | ||||||
|                 where totalrows = fmap (row "") . multiBalanceRowAsTableText opts $ tr |       | otherwise = | ||||||
|  |         let totalrows = multiBalanceRowAsTableText opts tr | ||||||
|  |             rh = Tab.Group NoLine $ map Header (replicate (length totalrows) "") | ||||||
|  |             ch = Header [] -- ignored | ||||||
|  |          in (flip (concatTables SingleLine) $ Table rh ch totalrows) | ||||||
|     maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals) |     maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals) | ||||||
|                    | otherwise       = id |                    | otherwise       = id | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -14,7 +14,6 @@ module Hledger.Cli.CompoundBalanceCommand ( | |||||||
|  ,compoundBalanceCommand |  ,compoundBalanceCommand | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
| import Data.Function ((&)) |  | ||||||
| import Data.List (foldl') | import Data.List (foldl') | ||||||
| import Data.Maybe (fromMaybe, mapMaybe) | import Data.Maybe (fromMaybe, mapMaybe) | ||||||
| import qualified Data.Text as T | import qualified Data.Text as T | ||||||
| @ -87,6 +86,8 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} = | |||||||
|     ,flagNone ["pretty-tables"] (setboolopt "pretty-tables") "use unicode when displaying tables" |     ,flagNone ["pretty-tables"] (setboolopt "pretty-tables") "use unicode when displaying tables" | ||||||
|     ,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name" |     ,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name" | ||||||
|     ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" |     ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" | ||||||
|  |     ,flagNone ["commodity-column"] (setboolopt "commodity-column") | ||||||
|  |       "show commodity symbols in a separate column, amounts as bare numbers, one row per commodity" | ||||||
|     ,outputFormatFlag ["txt","html","csv","json"] |     ,outputFormatFlag ["txt","html","csv","json"] | ||||||
|     ,outputFileFlag |     ,outputFileFlag | ||||||
|     ,commodityStyleFlag |     ,commodityStyleFlag | ||||||
| @ -213,13 +214,15 @@ compoundBalanceReportAsText ropts | |||||||
|     bigtable = |     bigtable = | ||||||
|       case map (subreportAsTable ropts) subreports of |       case map (subreportAsTable ropts) subreports of | ||||||
|         []   -> Tab.empty |         []   -> Tab.empty | ||||||
|         r:rs -> foldl' concatTables r rs |         r:rs -> foldl' (concatTables DoubleLine) r rs | ||||||
|     bigtable' |     bigtable' | ||||||
|       | no_total_ ropts || length subreports == 1 = |       | no_total_ ropts || length subreports == 1 = | ||||||
|           bigtable |           bigtable | ||||||
|       | otherwise = |       | otherwise = | ||||||
|           foldl (&) bigtable . zipWith ($) ((flip (+====+) . row "Net:") : repeat (flip (+.+) . row "")) |         let totalrows = multiBalanceRowAsTableText ropts netrow | ||||||
|             $ multiBalanceRowAsTableText ropts netrow |             rh = Tab.Group NoLine $ map Header ("Net:" : replicate (length totalrows - 1) "") | ||||||
|  |             ch = Header [] -- ignored | ||||||
|  |          in ((concatTables DoubleLine) bigtable $ Table rh ch totalrows) | ||||||
| 
 | 
 | ||||||
|     -- | Convert a named multi balance report to a table suitable for |     -- | Convert a named multi balance report to a table suitable for | ||||||
|     -- concatenating with others to make a compound balance report table. |     -- concatenating with others to make a compound balance report table. | ||||||
| @ -230,20 +233,17 @@ compoundBalanceReportAsText ropts | |||||||
|         -- tweak the layout |         -- tweak the layout | ||||||
|         t = Table (Tab.Group SingleLine [Header title, lefthdrs]) tophdrs ([]:cells) |         t = Table (Tab.Group SingleLine [Header title, lefthdrs]) tophdrs ([]:cells) | ||||||
| 
 | 
 | ||||||
| -- | Add the second table below the first, discarding its column headings. |  | ||||||
| concatTables (Table hLeft hTop dat) (Table hLeft' _ dat') = |  | ||||||
|     Table (Tab.Group DoubleLine [hLeft, hLeft']) hTop (dat ++ dat') |  | ||||||
| 
 |  | ||||||
| -- | Render a compound balance report as CSV. | -- | Render a compound balance report as CSV. | ||||||
| -- Subreports' CSV is concatenated, with the headings rows replaced by a | -- Subreports' CSV is concatenated, with the headings rows replaced by a | ||||||
| -- subreport title row, and an overall title row, one headings row, and an | -- subreport title row, and an overall title row, one headings row, and an | ||||||
| -- optional overall totals row is added. | -- optional overall totals row is added. | ||||||
| compoundBalanceReportAsCsv :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV | compoundBalanceReportAsCsv :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV | ||||||
| compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg)) = | compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subreports netrow) = | ||||||
|     addtotals $ |     addtotals $ | ||||||
|       padRow title |       padRow title | ||||||
|       : ( "Account" |       : ( "Account" | ||||||
|         : map (reportPeriodName (balanceaccum_ ropts) colspans) colspans |         : ["Commodity" | commodity_column_ ropts] | ||||||
|  |         ++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans | ||||||
|         ++ (if row_total_ ropts then ["Total"] else []) |         ++ (if row_total_ ropts then ["Total"] else []) | ||||||
|         ++ (if average_ ropts then ["Average"] else []) |         ++ (if average_ ropts then ["Average"] else []) | ||||||
|         ) |         ) | ||||||
| @ -259,26 +259,20 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor | |||||||
|           | null subreports = 1 |           | null subreports = 1 | ||||||
|           | otherwise = |           | otherwise = | ||||||
|             (1 +) $ -- account name column |             (1 +) $ -- account name column | ||||||
|  |             (if commodity_column_ ropts then (1+) else id) $ | ||||||
|             (if row_total_ ropts then (1+) else id) $ |             (if row_total_ ropts then (1+) else id) $ | ||||||
|             (if average_ ropts then (1+) else id) $ |             (if average_ ropts then (1+) else id) $ | ||||||
|             maximum $ -- depends on non-null subreports |             maximum $ -- depends on non-null subreports | ||||||
|             map (length . prDates . second3) subreports |             map (length . prDates . second3) subreports | ||||||
|     addtotals |     addtotals | ||||||
|       | no_total_ ropts || length subreports == 1 = id |       | no_total_ ropts || length subreports == 1 = id | ||||||
|       | otherwise = (++ |       | otherwise = (++ fmap ("Net:" : ) (multiBalanceRowAsCsvText ropts netrow)) | ||||||
|           ["Net:" : |  | ||||||
|            map (wbToText . showMixedAmountB oneLine) ( |  | ||||||
|              coltotals |  | ||||||
|              ++ (if row_total_ ropts then [grandtotal] else []) |  | ||||||
|              ++ (if average_ ropts   then [grandavg]   else []) |  | ||||||
|              ) |  | ||||||
|           ]) |  | ||||||
| 
 | 
 | ||||||
| -- | Render a compound balance report as HTML. | -- | Render a compound balance report as HTML. | ||||||
| compoundBalanceReportAsHtml :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> Html () | compoundBalanceReportAsHtml :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> Html () | ||||||
| compoundBalanceReportAsHtml ropts cbr = | compoundBalanceReportAsHtml ropts cbr = | ||||||
|   let |   let | ||||||
|     CompoundPeriodicReport title colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg) = cbr |     CompoundPeriodicReport title colspans subreports netrow = cbr | ||||||
|     colspanattr = colspan_ $ T.pack $ show $ |     colspanattr = colspan_ $ T.pack $ show $ | ||||||
|       1 + length colspans + (if row_total_ ropts then 1 else 0) + (if average_ ropts then 1 else 0) |       1 + length colspans + (if row_total_ ropts then 1 else 0) + (if average_ ropts then 1 else 0) | ||||||
|     leftattr = style_ "text-align:left" |     leftattr = style_ "text-align:left" | ||||||
| @ -287,7 +281,7 @@ compoundBalanceReportAsHtml ropts cbr = | |||||||
|     titlerows = |     titlerows = | ||||||
|          [tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title] |          [tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title] | ||||||
|       ++ [thRow $ |       ++ [thRow $ | ||||||
|           "" : |           "" : ["Commodity" | commodity_column_ ropts] ++ | ||||||
|           map (reportPeriodName (balanceaccum_ ropts) colspans) colspans |           map (reportPeriodName (balanceaccum_ ropts) colspans) colspans | ||||||
|           ++ (if row_total_ ropts then ["Total"] else []) |           ++ (if row_total_ ropts then ["Total"] else []) | ||||||
|           ++ (if average_ ropts then ["Average"] else []) |           ++ (if average_ ropts then ["Average"] else []) | ||||||
| @ -309,14 +303,7 @@ compoundBalanceReportAsHtml ropts cbr = | |||||||
|         ++ [blankrow] |         ++ [blankrow] | ||||||
| 
 | 
 | ||||||
|     totalrows | no_total_ ropts || length subreports == 1 = [] |     totalrows | no_total_ ropts || length subreports == 1 = [] | ||||||
|               | otherwise = |       | otherwise = multiBalanceReportHtmlFootRow ropts <$> (fmap ("Net:" :) $ multiBalanceRowAsCsvText ropts netrow) | ||||||
|                   let defstyle = style_ "text-align:right" |  | ||||||
|                       orEmpty b x = if b then x else mempty |  | ||||||
|                   in [tr_ $ th_ [class_ "", style_ "text-align:left"] "Net:" |  | ||||||
|                          <> foldMap (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack . showMixedAmountB oneLine) coltotals |  | ||||||
|                          <> orEmpty (row_total_ ropts) (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack $ showMixedAmountB oneLine grandtotal) |  | ||||||
|                          <> orEmpty (average_ ropts) (th_ [class_ "amount colaverage", defstyle] . toHtml . wbUnpack $ showMixedAmountB oneLine grandavg) |  | ||||||
|                     ] |  | ||||||
|   in do |   in do | ||||||
|     style_ (T.unlines ["" |     style_ (T.unlines ["" | ||||||
|       ,"td { padding:0 0.5em; }" |       ,"td { padding:0 0.5em; }" | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user