fix: bal: handle transpose flag with commodity-columns (#1654)
The textual output needs to be fully transposed instead of just the cell values. The multi-period csv handling code already does the right thing so just use those values. The change in CompoundBalanceCommand.hs is just to match signatures since commodity-column is not yet enabled there.
This commit is contained in:
parent
44e1ea10fa
commit
a3c0c0cade
@ -246,6 +246,7 @@ module Hledger.Cli.Commands.Balance (
|
|||||||
,balanceReportAsText
|
,balanceReportAsText
|
||||||
,balanceReportAsCsv
|
,balanceReportAsCsv
|
||||||
,balanceReportItemAsText
|
,balanceReportItemAsText
|
||||||
|
,multiBalanceRowAsTableText
|
||||||
,multiBalanceReportAsText
|
,multiBalanceReportAsText
|
||||||
,multiBalanceReportAsCsv
|
,multiBalanceReportAsCsv
|
||||||
,multiBalanceReportAsHtml
|
,multiBalanceReportAsHtml
|
||||||
@ -256,6 +257,7 @@ module Hledger.Cli.Commands.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
|
||||||
@ -517,28 +519,12 @@ multiBalanceReportAsCsv' opts@ReportOpts{..}
|
|||||||
++ ["total" | row_total_]
|
++ ["total" | row_total_]
|
||||||
++ ["average" | average_]
|
++ ["average" | average_]
|
||||||
) :
|
) :
|
||||||
concatMap (rowAsTexts (accountNameDrop drop_ . prrFullName)) items
|
concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items
|
||||||
where
|
where
|
||||||
rowAsTexts render row@(PeriodicReportRow _ as rowtot rowavg)
|
fullRowAsTexts render row = fmap ((:) (render row)) $ multiBalanceRowAsCsvText opts row
|
||||||
| not commodity_column_ = [render row : fmap (wbToText . showMixedAmountB bopts) all]
|
|
||||||
| otherwise =
|
|
||||||
joinNames . zipWith (:) cs -- add symbols and names
|
|
||||||
. transpose -- each row becomes a list of Text quantities
|
|
||||||
. fmap (fmap wbToText . showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
|
||||||
$ all
|
|
||||||
where
|
|
||||||
bopts = balanceOpts False opts
|
|
||||||
cs = S.toList . foldl' S.union mempty $ fmap maCommodities $ rowtot : rowavg : as
|
|
||||||
all = as
|
|
||||||
++ [rowtot | row_total_]
|
|
||||||
++ [rowavg | average_]
|
|
||||||
|
|
||||||
joinNames = fmap ((:) (render row))
|
|
||||||
|
|
||||||
totalrows :: [[T.Text]]
|
|
||||||
totalrows
|
totalrows
|
||||||
| no_total_ = mempty
|
| no_total_ = mempty
|
||||||
| otherwise = rowAsTexts (const "total") tr
|
| otherwise = fullRowAsTexts (const "total") tr
|
||||||
|
|
||||||
-- | Render a multi-column balance report as HTML.
|
-- | Render a multi-column balance report as HTML.
|
||||||
multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html ()
|
multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html ()
|
||||||
@ -665,33 +651,30 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $
|
|||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
-- | Build a 'Table' from a multi-column balance report.
|
-- | Build a 'Table' from a multi-column balance report.
|
||||||
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text MixedAmount
|
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text WideBuilder
|
||||||
balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
||||||
(PeriodicReport spans items (PeriodicReportRow _ coltotals tot avg)) =
|
(PeriodicReport spans items tr) =
|
||||||
maybetranspose $
|
maybetranspose $
|
||||||
addtotalrow $
|
addtotalrow $
|
||||||
Table
|
Table
|
||||||
(Tab.Group NoLine $ map Header accts)
|
(Tab.Group NoLine $ map Header (concat accts))
|
||||||
(Tab.Group NoLine $ map Header colheadings)
|
(Tab.Group NoLine $ map Header colheadings)
|
||||||
(map rowvals items)
|
(concat rows)
|
||||||
where
|
where
|
||||||
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
colheadings = ["Commodity" | commodity_column_ opts]
|
colheadings = ["Commodity" | commodity_column_ opts]
|
||||||
++ map (reportPeriodName balanceaccum_ spans) spans
|
++ map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | totalscolumn]
|
++ [" Total" | totalscolumn]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
accts = map renderacct items
|
fullRowAsTexts row =
|
||||||
|
let rs = multiBalanceRowAsTableText opts row
|
||||||
|
in (replicate (length rs) (renderacct row), rs)
|
||||||
|
(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
|
||||||
rowvals (PeriodicReportRow _ as rowtot rowavg) = as
|
|
||||||
++ [rowtot | totalscolumn]
|
|
||||||
++ [rowavg | average_]
|
|
||||||
addtotalrow | no_total_ opts = id
|
addtotalrow | no_total_ opts = id
|
||||||
| otherwise = (+----+ (row "" $
|
| otherwise = \tab -> foldl (&) tab . zipWith ($) (flip (+----+) : repeat (flip (+.+))) $ totalrows
|
||||||
coltotals
|
where totalrows = fmap (row "") . multiBalanceRowAsTableText opts $ tr
|
||||||
++ [tot | totalscolumn && not (null coltotals)]
|
|
||||||
++ [avg | average_ && not (null coltotals)]
|
|
||||||
))
|
|
||||||
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
|
||||||
|
|
||||||
@ -699,25 +682,41 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
-- made using 'balanceReportAsTable'), render it in a format suitable for
|
-- made using 'balanceReportAsTable'), render it in a format suitable for
|
||||||
-- console output. Amounts with more than two commodities will be elided
|
-- console output. Amounts with more than two commodities will be elided
|
||||||
-- unless --no-elide is used.
|
-- unless --no-elide is used.
|
||||||
balanceReportTableAsText :: ReportOpts -> Table T.Text T.Text MixedAmount -> TB.Builder
|
balanceReportTableAsText :: ReportOpts -> Table T.Text T.Text WideBuilder -> TB.Builder
|
||||||
balanceReportTableAsText ropts@ReportOpts{..} =
|
balanceReportTableAsText ReportOpts{..} =
|
||||||
Tab.renderTableByRowsB def{tableBorders=False, prettyTable=pretty_tables_} renderCh renderRow
|
Tab.renderTableByRowsB def{tableBorders=False, prettyTable=pretty_tables_} renderCh renderRow
|
||||||
where
|
where
|
||||||
renderCh
|
renderCh
|
||||||
| not commodity_column_ = fmap (Tab.textCell TopRight)
|
| not commodity_column_ || transpose_ = fmap (Tab.textCell TopRight)
|
||||||
| otherwise = zipWith ($) (Tab.textCell TopLeft : repeat (Tab.textCell TopRight))
|
| otherwise = zipWith ($) (Tab.textCell TopLeft : repeat (Tab.textCell TopRight))
|
||||||
|
|
||||||
renderRow :: (T.Text, [MixedAmount]) -> (Cell, [Cell])
|
renderRow :: (T.Text, [WideBuilder]) -> (Cell, [Cell])
|
||||||
renderRow (rh, row)
|
renderRow (rh, row)
|
||||||
| not commodity_column_ =
|
| not commodity_column_ || transpose_ =
|
||||||
(Tab.textCell TopLeft rh, fmap (Cell TopRight . pure . showMixedAmountB bopts) row)
|
(Tab.textCell TopLeft rh, fmap (Cell TopRight . pure) row)
|
||||||
| otherwise =
|
| otherwise =
|
||||||
( Tab.textsCell TopLeft (replicate (length cs) rh)
|
(Tab.textCell TopLeft rh, zipWith ($) (Cell TopLeft : repeat (Cell TopRight)) (fmap pure row))
|
||||||
, Tab.textsCell TopLeft cs
|
|
||||||
: fmap (Cell TopRight . showMixedAmountLinesB bopts{displayOrder = Just cs}) row)
|
multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
|
||||||
|
multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg)
|
||||||
|
| not commodity_column_ = [fmap (showMixedAmountB bopts) all]
|
||||||
|
| otherwise =
|
||||||
|
zipWith (:) (fmap wbFromText cs) -- add symbols
|
||||||
|
. transpose -- each row becomes a list of Text quantities
|
||||||
|
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
||||||
|
$ all
|
||||||
where
|
where
|
||||||
bopts = balanceOpts True ropts
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
cs = S.toList . foldl' S.union mempty $ fmap maCommodities row
|
cs = S.toList . foldl' S.union mempty $ fmap maCommodities all
|
||||||
|
all = as
|
||||||
|
++ [rowtot | totalscolumn && not (null as)]
|
||||||
|
++ [rowavg | average_ && not (null as)]
|
||||||
|
|
||||||
|
multiBalanceRowAsCsvText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[T.Text]]
|
||||||
|
multiBalanceRowAsCsvText opts = fmap (fmap wbToText) . multiBalanceRowAsWbs (balanceOpts False opts) opts
|
||||||
|
|
||||||
|
multiBalanceRowAsTableText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
|
||||||
|
multiBalanceRowAsTableText opts = multiBalanceRowAsWbs (balanceOpts True opts) opts
|
||||||
|
|
||||||
-- | Amount display options to use for balance reports
|
-- | Amount display options to use for balance reports
|
||||||
balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
|
balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
|
||||||
|
|||||||
@ -14,6 +14,7 @@ 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
|
||||||
@ -204,7 +205,7 @@ Balance Sheet
|
|||||||
-}
|
-}
|
||||||
compoundBalanceReportAsText :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> TL.Text
|
compoundBalanceReportAsText :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> TL.Text
|
||||||
compoundBalanceReportAsText ropts
|
compoundBalanceReportAsText ropts
|
||||||
(CompoundPeriodicReport title _colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg)) =
|
(CompoundPeriodicReport title _colspans subreports netrow) =
|
||||||
TB.toLazyText $
|
TB.toLazyText $
|
||||||
TB.fromText title <> TB.fromText "\n\n" <>
|
TB.fromText title <> TB.fromText "\n\n" <>
|
||||||
balanceReportTableAsText ropts bigtable'
|
balanceReportTableAsText ropts bigtable'
|
||||||
@ -217,13 +218,8 @@ compoundBalanceReportAsText ropts
|
|||||||
| no_total_ ropts || length subreports == 1 =
|
| no_total_ ropts || length subreports == 1 =
|
||||||
bigtable
|
bigtable
|
||||||
| otherwise =
|
| otherwise =
|
||||||
bigtable
|
foldl (&) bigtable . zipWith ($) ((flip (+====+) . row "Net:") : repeat (flip (+.+) . row ""))
|
||||||
+====+
|
$ multiBalanceRowAsTableText ropts netrow
|
||||||
row "Net:" (
|
|
||||||
coltotals
|
|
||||||
++ (if row_total_ ropts then [grandtotal] else [])
|
|
||||||
++ (if average_ ropts then [grandavg] else [])
|
|
||||||
)
|
|
||||||
|
|
||||||
-- | 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.
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user