@@ -307,7 +307,7 @@ import Hledger.Write.Ods (printFods)
307307import Hledger.Write.Html (Html , styledTableHtml , htmlAsLazyText , toHtml )
308308import Hledger.Write.Spreadsheet (rawTableContent , headerCell ,
309309 addHeaderBorders , addRowSpanHeader ,
310- cellFromMixedAmount , cellsFromMixedAmount )
310+ cellFromMixedAmount , cellsFromMixedAmount , cellFromAmount )
311311import qualified Hledger.Write.Spreadsheet as Ods
312312
313313
@@ -593,6 +593,9 @@ renderComponent topaligned oneline opts (acctname, dep, total) (FormatField ljus
593593 }
594594
595595
596+ headerWithoutBorders :: [Ods. Cell () text ] -> [Ods. Cell Ods. NumLines text ]
597+ headerWithoutBorders = map (\ c -> c {Ods. cellBorder = Ods. noBorder})
598+
596599simpleDateSpanCell :: DateSpan -> Ods. Cell Ods. NumLines Text
597600simpleDateSpanCell = Ods. defaultCell . showDateSpan
598601
@@ -621,8 +624,11 @@ balanceReportAsSpreadsheet opts (items, total) =
621624 headers =
622625 addHeaderBorders $ map headerCell $
623626 " account" : case layout_ opts of
627+ LayoutBareWide -> allCommodities
624628 LayoutBare -> [" commodity" , " balance" ]
625629 _ -> [" balance" ]
630+ allCommodities =
631+ S. toAscList $ foldMap (\ (_,_,_,ma) -> maCommodities ma) items
626632 rows ::
627633 RowClass -> BalanceReportItem ->
628634 [[Ods. Cell Ods. NumLines Text ]]
@@ -634,6 +640,15 @@ balanceReportAsSpreadsheet opts (items, total) =
634640 cell $ renderBalanceAcct opts nbsp (name, dispName, dep) in
635641 addRowSpanHeader accountCell $
636642 case layout_ opts of
643+ LayoutBareWide ->
644+ let bopts =
645+ machineFmt {
646+ displayCommodity = False ,
647+ displayCommodityOrder = Just allCommodities
648+ } in
649+ [map (\ bldAmt ->
650+ fmap wbToText $ cellFromAmount bopts (amountClass rc, bldAmt)) $
651+ showMixedAmountLinesPartsB bopts ma]
637652 LayoutBare ->
638653 map (\ a -> [cell $ acommodity a, renderAmount rc $ mixedAmount a])
639654 . amounts $ mixedAmountStripCosts ma
@@ -657,29 +672,41 @@ balanceReportAsSpreadsheet opts (items, total) =
657672multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV
658673multiBalanceReportAsCsv opts@ ReportOpts {.. } report =
659674 (if transpose_ then transpose else id ) $
660- rawTableContent $ header : body ++ totals
675+ rawTableContent $ header ++ body ++ totals
661676 where
662677 (header, body, totals) =
663- multiBalanceReportAsSpreadsheetParts machineFmt opts report
678+ multiBalanceReportAsSpreadsheetParts machineFmt opts
679+ (allCommoditiesFromPeriodicReport $ prRows report) report
664680
665681-- | Render the Spreadsheet table rows (CSV, ODS, HTML) for a MultiBalanceReport.
666682-- Returns the heading row, 0 or more body rows, and the totals row if enabled.
667683multiBalanceReportAsSpreadsheetParts ::
668- AmountFormat -> ReportOpts -> MultiBalanceReport ->
669- ([Ods. Cell Ods. NumLines Text ],
684+ AmountFormat -> ReportOpts ->
685+ [CommoditySymbol ] -> MultiBalanceReport ->
686+ ([[Ods. Cell Ods. NumLines Text ]],
670687 [[Ods. Cell Ods. NumLines Text ]],
671688 [[Ods. Cell Ods. NumLines Text ]])
672- multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. } (PeriodicReport colspans items tr) =
673- (headers, concatMap fullRowAsTexts items, addTotalBorders totalrows)
689+ multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. }
690+ allCommodities (PeriodicReport colspans items tr) =
691+ (allHeaders, concatMap fullRowAsTexts items, addTotalBorders totalrows)
674692 where
675693 accountCell label =
676694 (Ods. defaultCell label) {Ods. cellClass = Ods. Class " account" }
677695 hCell cls label = (headerCell label) {Ods. cellClass = Ods. Class cls}
696+ allHeaders =
697+ case layout_ of
698+ LayoutBareWide ->
699+ [headerWithoutBorders $
700+ Ods. emptyCell :
701+ concatMap (Ods. horizontalSpan allCommodities) dateHeaders,
702+ headers]
703+ _ -> [headers]
678704 headers =
679705 addHeaderBorders $
680706 hCell " account" " account" :
681707 case layout_ of
682708 LayoutTidy -> map headerCell tidyColumnLabels
709+ LayoutBareWide -> dateHeaders >> map headerCell allCommodities
683710 LayoutBare -> headerCell " commodity" : dateHeaders
684711 _ -> dateHeaders
685712 dateHeaders =
@@ -700,7 +727,7 @@ multiBalanceReportAsSpreadsheetParts fmt opts@ReportOpts{..} (PeriodicReport col
700727 rowAsText Total simpleDateSpanCell tr
701728 rowAsText rc dsCell =
702729 map (map (fmap wbToText)) .
703- multiBalanceRowAsCellBuilders fmt opts colspans rc dsCell
730+ multiBalanceRowAsCellBuilders fmt opts colspans allCommodities rc dsCell
704731
705732tidyColumnLabels :: [Text ]
706733tidyColumnLabels =
@@ -720,10 +747,12 @@ multiBalanceReportAsSpreadsheet ::
720747 ((Int , Int ), [[Ods. Cell Ods. NumLines Text ]])
721748multiBalanceReportAsSpreadsheet ropts mbr =
722749 let (header,body,total) =
723- multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts mbr
750+ multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts
751+ (allCommoditiesFromPeriodicReport $ prRows mbr) mbr
724752 in (if transpose_ ropts then swap *** Ods. transpose else id ) $
725- ((1 , case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
726- header : body ++ total)
753+ ((case layout_ ropts of LayoutBareWide -> 2 ; _ -> 1 ,
754+ case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
755+ header ++ body ++ total)
727756
728757
729758-- | Render a multi-column balance report as plain text suitable for console output.
@@ -794,19 +823,24 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
794823 (concat rows)
795824 where
796825 colheadings = [" Commodity" | layout_ opts == LayoutBare ]
797- ++ (if not summary_only_ then map (reportPeriodName balanceaccum_ spans) spans else [] )
826+ ++ (if not summary_only_
827+ then case layout_ opts of
828+ LayoutBareWide -> spans >> allCommodities
829+ _ -> map (reportPeriodName balanceaccum_ spans) spans
830+ else [] )
798831 ++ [" Total" | multiBalanceHasTotalsColumn opts]
799832 ++ [" Average" | average_]
833+ allCommodities = allCommoditiesFromPeriodicReport items
800834 (accts, rows) = unzip $ fmap fullRowAsTexts items
801835 where
802836 fullRowAsTexts row = (replicate (length rs) (renderacct row), rs)
803837 where
804- rs = multiBalanceRowAsText opts row
838+ rs = multiBalanceRowAsText opts allCommodities row
805839 renderacct row' = T. replicate (prrIndent row' * 2 ) " " <> prrDisplayName row'
806840 addtotalrow
807841 | no_total_ opts = id
808842 | otherwise =
809- let totalrows = multiBalanceRowAsText opts tr
843+ let totalrows = multiBalanceRowAsText opts allCommodities tr
810844 rowhdrs = Group NoLine $ map Header $ totalRowHeadingText : replicate (length totalrows - 1 ) " "
811845 colhdrs = Header [] -- unused, concatTables will discard
812846 in (flip (concatTables SingleLine ) $ Table rowhdrs colhdrs totalrows)
@@ -815,12 +849,17 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
815849 multiColumnTableInterRowBorder = NoLine
816850 multiColumnTableInterColumnBorder = if pretty_ opts then SingleLine else NoLine
817851
852+ allCommoditiesFromPeriodicReport ::
853+ [PeriodicReportRow a MixedAmount ] -> [CommoditySymbol ]
854+ allCommoditiesFromPeriodicReport =
855+ S. toAscList . foldMap (foldMap maCommodities . prrAmounts)
856+
818857multiBalanceRowAsCellBuilders ::
819- AmountFormat -> ReportOpts -> [DateSpan ] ->
858+ AmountFormat -> ReportOpts -> [DateSpan ] -> [ CommoditySymbol ] ->
820859 RowClass -> (DateSpan -> Ods. Cell Ods. NumLines Text ) ->
821860 PeriodicReportRow a MixedAmount ->
822861 [[Ods. Cell Ods. NumLines WideBuilder ]]
823- multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans
862+ multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans allCommodities
824863 rc renderDateSpanCell (PeriodicReportRow _acct as rowtot rowavg) =
825864 case layout_ of
826865 LayoutWide width -> [fmap (cellFromMixedAmount bopts{displayMaxWidth= width}) clsamts]
@@ -831,6 +870,8 @@ multiBalanceRowAsCellBuilders bopts ropts@ReportOpts{..} colspans
831870 . transpose -- each row becomes a list of Text quantities
832871 . map (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just cs, displayMinWidth= Nothing })
833872 $ clsamts
873+ LayoutBareWide -> [concatMap (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just allCommodities, displayMinWidth= Nothing })
874+ $ clsamts]
834875 LayoutTidy -> concat
835876 . zipWith (map . addDateColumns) colspans
836877 . map ( zipWith (\ c a -> [wbCell c, a]) cs
@@ -873,16 +914,20 @@ multiBalanceHasTotalsColumn :: ReportOpts -> Bool
873914multiBalanceHasTotalsColumn ropts =
874915 row_total_ ropts && balanceaccum_ ropts `notElem` [Cumulative , Historical ]
875916
876- multiBalanceRowAsText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
877- multiBalanceRowAsText opts =
917+ multiBalanceRowAsText ::
918+ ReportOpts -> [CommoditySymbol ] -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
919+ multiBalanceRowAsText opts allCommodities =
878920 rawTableContent .
879- multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts} opts []
921+ multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts}
922+ opts [] allCommodities
880923 Value simpleDateSpanCell
881924
882- multiBalanceRowAsCsvText :: ReportOpts -> [DateSpan ] -> PeriodicReportRow a MixedAmount -> [[T. Text ]]
883- multiBalanceRowAsCsvText opts colspans =
925+ multiBalanceRowAsCsvText ::
926+ ReportOpts -> [DateSpan ] -> [CommoditySymbol ] ->
927+ PeriodicReportRow a MixedAmount -> [[T. Text ]]
928+ multiBalanceRowAsCsvText opts colspans allCommodities =
884929 map (map (wbToText . Ods. cellContent)) .
885- multiBalanceRowAsCellBuilders machineFmt opts colspans
930+ multiBalanceRowAsCellBuilders machineFmt opts colspans allCommodities
886931 Value simpleDateSpanCell
887932
888933
0 commit comments