@@ -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
@@ -598,6 +598,9 @@ renderComponent topaligned oneline opts (acctname, dep, total) (FormatField ljus
598598 }
599599
600600
601+ headerWithoutBorders :: [Ods. Cell () text ] -> [Ods. Cell Ods. NumLines text ]
602+ headerWithoutBorders = map (\ c -> c {Ods. cellBorder = Ods. noBorder})
603+
601604simpleDateSpanCell :: DateSpan -> Ods. Cell Ods. NumLines Text
602605simpleDateSpanCell = Ods. defaultCell . showDateSpan
603606
@@ -626,8 +629,11 @@ balanceReportAsSpreadsheet opts (items, total) =
626629 headers =
627630 addHeaderBorders $ map headerCell $
628631 " account" : case layout_ opts of
632+ LayoutBareWide -> allCommodities
629633 LayoutBare -> [" commodity" , " balance" ]
630634 _ -> [" balance" ]
635+ allCommodities =
636+ S. toAscList $ foldMap (\ (_,_,_,ma) -> maCommodities ma) items
631637 rows ::
632638 RowClass -> BalanceReportItem ->
633639 [[Ods. Cell Ods. NumLines Text ]]
@@ -639,6 +645,15 @@ balanceReportAsSpreadsheet opts (items, total) =
639645 cell $ renderBalanceAcct opts nbsp (name, dispName, dep) in
640646 addRowSpanHeader accountCell $
641647 case layout_ opts of
648+ LayoutBareWide ->
649+ let bopts =
650+ machineFmt {
651+ displayCommodity = False ,
652+ displayCommodityOrder = Just allCommodities
653+ } in
654+ [map (\ bldAmt ->
655+ fmap wbToText $ cellFromAmount bopts (amountClass rc, bldAmt)) $
656+ showMixedAmountLinesPartsB bopts ma]
642657 LayoutBare ->
643658 map (\ a -> [cell $ acommodity a, renderAmount rc $ mixedAmount a])
644659 . amounts $ mixedAmountStripCosts ma
@@ -662,29 +677,41 @@ balanceReportAsSpreadsheet opts (items, total) =
662677multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV
663678multiBalanceReportAsCsv opts@ ReportOpts {.. } report =
664679 (if transpose_ then transpose else id ) $
665- rawTableContent $ header : body ++ totals
680+ rawTableContent $ header ++ body ++ totals
666681 where
667682 (header, body, totals) =
668- multiBalanceReportAsSpreadsheetParts machineFmt opts report
683+ multiBalanceReportAsSpreadsheetParts machineFmt opts
684+ (allCommoditiesFromPeriodicReport $ prRows report) report
669685
670686-- | Render the Spreadsheet table rows (CSV, ODS, HTML) for a MultiBalanceReport.
671687-- Returns the heading row, 0 or more body rows, and the totals row if enabled.
672688multiBalanceReportAsSpreadsheetParts ::
673- AmountFormat -> ReportOpts -> MultiBalanceReport ->
674- ([Ods. Cell Ods. NumLines Text ],
689+ AmountFormat -> ReportOpts ->
690+ [CommoditySymbol ] -> MultiBalanceReport ->
691+ ([[Ods. Cell Ods. NumLines Text ]],
675692 [[Ods. Cell Ods. NumLines Text ]],
676693 [[Ods. Cell Ods. NumLines Text ]])
677- multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. } (PeriodicReport colspans items tr) =
678- (headers, concatMap fullRowAsTexts items, addTotalBorders totalrows)
694+ multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. }
695+ allCommodities (PeriodicReport colspans items tr) =
696+ (allHeaders, concatMap fullRowAsTexts items, addTotalBorders totalrows)
679697 where
680698 accountCell label =
681699 (Ods. defaultCell label) {Ods. cellClass = Ods. Class " account" }
682700 hCell cls label = (headerCell label) {Ods. cellClass = Ods. Class cls}
701+ allHeaders =
702+ case layout_ of
703+ LayoutBareWide ->
704+ [headerWithoutBorders $
705+ Ods. emptyCell :
706+ concatMap (Ods. horizontalSpan allCommodities) dateHeaders,
707+ headers]
708+ _ -> [headers]
683709 headers =
684710 addHeaderBorders $
685711 hCell " account" " account" :
686712 case layout_ of
687713 LayoutTidy -> map headerCell tidyColumnLabels
714+ LayoutBareWide -> dateHeaders >> map headerCell allCommodities
688715 LayoutBare -> headerCell " commodity" : dateHeaders
689716 _ -> dateHeaders
690717 dateHeaders =
@@ -705,7 +732,7 @@ multiBalanceReportAsSpreadsheetParts fmt opts@ReportOpts{..} (PeriodicReport col
705732 rowAsText Total simpleDateSpanCell tr
706733 rowAsText rc dsCell =
707734 map (map (fmap wbToText)) .
708- multiBalanceRowAsCellBuilders fmt opts colspans rc dsCell
735+ multiBalanceRowAsCellBuilders fmt opts colspans allCommodities rc dsCell
709736
710737tidyColumnLabels :: [Text ]
711738tidyColumnLabels =
@@ -725,10 +752,12 @@ multiBalanceReportAsSpreadsheet ::
725752 ((Int , Int ), [[Ods. Cell Ods. NumLines Text ]])
726753multiBalanceReportAsSpreadsheet ropts mbr =
727754 let (header,body,total) =
728- multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts mbr
755+ multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts
756+ (allCommoditiesFromPeriodicReport $ prRows mbr) mbr
729757 in (if transpose_ ropts then swap *** Ods. transpose else id ) $
730- ((1 , case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
731- header : body ++ total)
758+ ((case layout_ ropts of LayoutBareWide -> 2 ; _ -> 1 ,
759+ case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
760+ header ++ body ++ total)
732761
733762
734763-- | Render a multi-column balance report as plain text suitable for console output.
@@ -799,19 +828,24 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
799828 (concat rows)
800829 where
801830 colheadings = [" Commodity" | layout_ opts == LayoutBare ]
802- ++ (if not summary_only_ then map (reportPeriodName balanceaccum_ spans) spans else [] )
831+ ++ (if not summary_only_
832+ then case layout_ opts of
833+ LayoutBareWide -> spans >> allCommodities
834+ _ -> map (reportPeriodName balanceaccum_ spans) spans
835+ else [] )
803836 ++ [" Total" | multiBalanceHasTotalsColumn opts]
804837 ++ [" Average" | average_]
838+ allCommodities = allCommoditiesFromPeriodicReport items
805839 (accts, rows) = unzip $ fmap fullRowAsTexts items
806840 where
807841 fullRowAsTexts row = (replicate (length rs) (renderacct row), rs)
808842 where
809- rs = multiBalanceRowAsText opts row
843+ rs = multiBalanceRowAsText opts allCommodities row
810844 renderacct row' = T. replicate (prrIndent row' * 2 ) " " <> prrDisplayName row'
811845 addtotalrow
812846 | no_total_ opts = id
813847 | otherwise =
814- let totalrows = multiBalanceRowAsText opts tr
848+ let totalrows = multiBalanceRowAsText opts allCommodities tr
815849 rowhdrs = Group NoLine $ map Header $ totalRowHeadingText : replicate (length totalrows - 1 ) " "
816850 colhdrs = Header [] -- unused, concatTables will discard
817851 in (flip (concatTables SingleLine ) $ Table rowhdrs colhdrs totalrows)
@@ -820,12 +854,17 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
820854 multiColumnTableInterRowBorder = NoLine
821855 multiColumnTableInterColumnBorder = if pretty_ opts then SingleLine else NoLine
822856
857+ allCommoditiesFromPeriodicReport ::
858+ [PeriodicReportRow a MixedAmount ] -> [CommoditySymbol ]
859+ allCommoditiesFromPeriodicReport =
860+ S. toAscList . foldMap (foldMap maCommodities . prrAmounts)
861+
823862multiBalanceRowAsCellBuilders ::
824- AmountFormat -> ReportOpts -> [DateSpan ] ->
863+ AmountFormat -> ReportOpts -> [DateSpan ] -> [ CommoditySymbol ] ->
825864 RowClass -> (DateSpan -> Ods. Cell Ods. NumLines Text ) ->
826865 PeriodicReportRow a MixedAmount ->
827866 [[Ods. Cell Ods. NumLines WideBuilder ]]
828- multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans
867+ multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans allCommodities
829868 rc renderDateSpanCell (PeriodicReportRow _acct as rowtot rowavg) =
830869 case layout_ of
831870 LayoutWide width -> [fmap (cellFromMixedAmount bopts{displayMaxWidth= width}) clsamts]
@@ -836,6 +875,8 @@ multiBalanceRowAsCellBuilders bopts ropts@ReportOpts{..} colspans
836875 . transpose -- each row becomes a list of Text quantities
837876 . map (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just cs, displayMinWidth= Nothing })
838877 $ clsamts
878+ LayoutBareWide -> [concatMap (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just allCommodities, displayMinWidth= Nothing })
879+ $ clsamts]
839880 LayoutTidy -> concat
840881 . zipWith (map . addDateColumns) colspans
841882 . map ( zipWith (\ c a -> [wbCell c, a]) cs
@@ -878,16 +919,20 @@ multiBalanceHasTotalsColumn :: ReportOpts -> Bool
878919multiBalanceHasTotalsColumn ropts =
879920 row_total_ ropts && balanceaccum_ ropts `notElem` [Cumulative , Historical ]
880921
881- multiBalanceRowAsText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
882- multiBalanceRowAsText opts =
922+ multiBalanceRowAsText ::
923+ ReportOpts -> [CommoditySymbol ] -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
924+ multiBalanceRowAsText opts allCommodities =
883925 rawTableContent .
884- multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts} opts []
926+ multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts}
927+ opts [] allCommodities
885928 Value simpleDateSpanCell
886929
887- multiBalanceRowAsCsvText :: ReportOpts -> [DateSpan ] -> PeriodicReportRow a MixedAmount -> [[T. Text ]]
888- multiBalanceRowAsCsvText opts colspans =
930+ multiBalanceRowAsCsvText ::
931+ ReportOpts -> [DateSpan ] -> [CommoditySymbol ] ->
932+ PeriodicReportRow a MixedAmount -> [[T. Text ]]
933+ multiBalanceRowAsCsvText opts colspans allCommodities =
889934 map (map (wbToText . Ods. cellContent)) .
890- multiBalanceRowAsCellBuilders machineFmt opts colspans
935+ multiBalanceRowAsCellBuilders machineFmt opts colspans allCommodities
891936 Value simpleDateSpanCell
892937
893938
0 commit comments