@@ -308,7 +308,7 @@ import Hledger.Write.Ods (printFods)
308308import Hledger.Write.Html.Lucid (printHtml )
309309import Hledger.Write.Spreadsheet (rawTableContent , headerCell ,
310310 addHeaderBorders , addRowSpanHeader ,
311- cellFromMixedAmount , cellsFromMixedAmount )
311+ cellFromMixedAmount , cellsFromMixedAmount , cellFromAmount )
312312import qualified Hledger.Write.Spreadsheet as Ods
313313
314314
@@ -594,6 +594,9 @@ renderComponent topaligned oneline opts (acctname, dep, total) (FormatField ljus
594594 }
595595
596596
597+ headerWithoutBorders :: [Ods. Cell () text ] -> [Ods. Cell Ods. NumLines text ]
598+ headerWithoutBorders = map (\ c -> c {Ods. cellBorder = Ods. noBorder})
599+
597600simpleDateSpanCell :: DateSpan -> Ods. Cell Ods. NumLines Text
598601simpleDateSpanCell = Ods. defaultCell . showDateSpan
599602
@@ -622,8 +625,11 @@ balanceReportAsSpreadsheet opts (items, total) =
622625 headers =
623626 addHeaderBorders $ map headerCell $
624627 " account" : case layout_ opts of
628+ LayoutBareWide -> allCommodities
625629 LayoutBare -> [" commodity" , " balance" ]
626630 _ -> [" balance" ]
631+ allCommodities =
632+ S. toAscList $ foldMap (\ (_,_,_,ma) -> maCommodities ma) items
627633 rows ::
628634 RowClass -> BalanceReportItem ->
629635 [[Ods. Cell Ods. NumLines Text ]]
@@ -635,6 +641,15 @@ balanceReportAsSpreadsheet opts (items, total) =
635641 cell $ renderBalanceAcct opts nbsp (name, dispName, dep) in
636642 addRowSpanHeader accountCell $
637643 case layout_ opts of
644+ LayoutBareWide ->
645+ let bopts =
646+ machineFmt {
647+ displayCommodity = False ,
648+ displayCommodityOrder = Just allCommodities
649+ } in
650+ [map (\ bldAmt ->
651+ fmap wbToText $ cellFromAmount bopts (amountClass rc, bldAmt)) $
652+ showMixedAmountLinesPartsB bopts ma]
638653 LayoutBare ->
639654 map (\ a -> [cell $ acommodity a, renderAmount rc $ mixedAmount a])
640655 . amounts $ mixedAmountStripCosts ma
@@ -658,29 +673,41 @@ balanceReportAsSpreadsheet opts (items, total) =
658673multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV
659674multiBalanceReportAsCsv opts@ ReportOpts {.. } report =
660675 (if transpose_ then transpose else id ) $
661- rawTableContent $ header : body ++ totals
676+ rawTableContent $ header ++ body ++ totals
662677 where
663678 (header, body, totals) =
664- multiBalanceReportAsSpreadsheetParts machineFmt opts report
679+ multiBalanceReportAsSpreadsheetParts machineFmt opts
680+ (allCommoditiesFromPeriodicReport $ prRows report) report
665681
666682-- | Render the Spreadsheet table rows (CSV, ODS, HTML) for a MultiBalanceReport.
667683-- Returns the heading row, 0 or more body rows, and the totals row if enabled.
668684multiBalanceReportAsSpreadsheetParts ::
669- AmountFormat -> ReportOpts -> MultiBalanceReport ->
670- ([Ods. Cell Ods. NumLines Text ],
685+ AmountFormat -> ReportOpts ->
686+ [CommoditySymbol ] -> MultiBalanceReport ->
687+ ([[Ods. Cell Ods. NumLines Text ]],
671688 [[Ods. Cell Ods. NumLines Text ]],
672689 [[Ods. Cell Ods. NumLines Text ]])
673- multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. } (PeriodicReport colspans items tr) =
674- (headers, concatMap fullRowAsTexts items, addTotalBorders totalrows)
690+ multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. }
691+ allCommodities (PeriodicReport colspans items tr) =
692+ (allHeaders, concatMap fullRowAsTexts items, addTotalBorders totalrows)
675693 where
676694 accountCell label =
677695 (Ods. defaultCell label) {Ods. cellClass = Ods. Class " account" }
678696 hCell cls label = (headerCell label) {Ods. cellClass = Ods. Class cls}
697+ allHeaders =
698+ case layout_ of
699+ LayoutBareWide ->
700+ [headerWithoutBorders $
701+ Ods. emptyCell :
702+ concatMap (Ods. horizontalSpan allCommodities) dateHeaders,
703+ headers]
704+ _ -> [headers]
679705 headers =
680706 addHeaderBorders $
681707 hCell " account" " account" :
682708 case layout_ of
683709 LayoutTidy -> map headerCell tidyColumnLabels
710+ LayoutBareWide -> dateHeaders >> map headerCell allCommodities
684711 LayoutBare -> headerCell " commodity" : dateHeaders
685712 _ -> dateHeaders
686713 dateHeaders =
@@ -701,7 +728,7 @@ multiBalanceReportAsSpreadsheetParts fmt opts@ReportOpts{..} (PeriodicReport col
701728 rowAsText Total simpleDateSpanCell tr
702729 rowAsText rc dsCell =
703730 map (map (fmap wbToText)) .
704- multiBalanceRowAsCellBuilders fmt opts colspans rc dsCell
731+ multiBalanceRowAsCellBuilders fmt opts colspans allCommodities rc dsCell
705732
706733tidyColumnLabels :: [Text ]
707734tidyColumnLabels =
@@ -721,10 +748,12 @@ multiBalanceReportAsSpreadsheet ::
721748 ((Int , Int ), [[Ods. Cell Ods. NumLines Text ]])
722749multiBalanceReportAsSpreadsheet ropts mbr =
723750 let (header,body,total) =
724- multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts mbr
751+ multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts
752+ (allCommoditiesFromPeriodicReport $ prRows mbr) mbr
725753 in (if transpose_ ropts then swap *** Ods. transpose else id ) $
726- ((1 , case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
727- header : body ++ total)
754+ ((case layout_ ropts of LayoutBareWide -> 2 ; _ -> 1 ,
755+ case layout_ ropts of LayoutWide _ -> 1 ; _ -> 0 ),
756+ header ++ body ++ total)
728757
729758
730759-- | Render a multi-column balance report as plain text suitable for console output.
@@ -795,19 +824,24 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
795824 (concat rows)
796825 where
797826 colheadings = [" Commodity" | layout_ opts == LayoutBare ]
798- ++ (if not summary_only_ then map (reportPeriodName balanceaccum_ spans) spans else [] )
827+ ++ (if not summary_only_
828+ then case layout_ opts of
829+ LayoutBareWide -> spans >> allCommodities
830+ _ -> map (reportPeriodName balanceaccum_ spans) spans
831+ else [] )
799832 ++ [" Total" | multiBalanceHasTotalsColumn opts]
800833 ++ [" Average" | average_]
834+ allCommodities = allCommoditiesFromPeriodicReport items
801835 (accts, rows) = unzip $ fmap fullRowAsTexts items
802836 where
803837 fullRowAsTexts row = (replicate (length rs) (renderacct row), rs)
804838 where
805- rs = multiBalanceRowAsText opts row
839+ rs = multiBalanceRowAsText opts allCommodities row
806840 renderacct row' = T. replicate (prrIndent row' * 2 ) " " <> prrDisplayName row'
807841 addtotalrow
808842 | no_total_ opts = id
809843 | otherwise =
810- let totalrows = multiBalanceRowAsText opts tr
844+ let totalrows = multiBalanceRowAsText opts allCommodities tr
811845 rowhdrs = Group NoLine $ map Header $ totalRowHeadingText : replicate (length totalrows - 1 ) " "
812846 colhdrs = Header [] -- unused, concatTables will discard
813847 in (flip (concatTables SingleLine ) $ Table rowhdrs colhdrs totalrows)
@@ -816,12 +850,17 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, balanceaccum_
816850 multiColumnTableInterRowBorder = NoLine
817851 multiColumnTableInterColumnBorder = if pretty_ opts then SingleLine else NoLine
818852
853+ allCommoditiesFromPeriodicReport ::
854+ [PeriodicReportRow a MixedAmount ] -> [CommoditySymbol ]
855+ allCommoditiesFromPeriodicReport =
856+ S. toAscList . foldMap (foldMap maCommodities . prrAmounts)
857+
819858multiBalanceRowAsCellBuilders ::
820- AmountFormat -> ReportOpts -> [DateSpan ] ->
859+ AmountFormat -> ReportOpts -> [DateSpan ] -> [ CommoditySymbol ] ->
821860 RowClass -> (DateSpan -> Ods. Cell Ods. NumLines Text ) ->
822861 PeriodicReportRow a MixedAmount ->
823862 [[Ods. Cell Ods. NumLines WideBuilder ]]
824- multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans
863+ multiBalanceRowAsCellBuilders bopts ropts@ ReportOpts {.. } colspans allCommodities
825864 rc renderDateSpanCell (PeriodicReportRow _acct as rowtot rowavg) =
826865 case layout_ of
827866 LayoutWide width -> [fmap (cellFromMixedAmount bopts{displayMaxWidth= width}) clsamts]
@@ -832,6 +871,8 @@ multiBalanceRowAsCellBuilders bopts ropts@ReportOpts{..} colspans
832871 . transpose -- each row becomes a list of Text quantities
833872 . map (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just cs, displayMinWidth= Nothing })
834873 $ clsamts
874+ LayoutBareWide -> [concatMap (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just allCommodities, displayMinWidth= Nothing })
875+ $ clsamts]
835876 LayoutTidy -> concat
836877 . zipWith (map . addDateColumns) colspans
837878 . map ( zipWith (\ c a -> [wbCell c, a]) cs
@@ -874,16 +915,20 @@ multiBalanceHasTotalsColumn :: ReportOpts -> Bool
874915multiBalanceHasTotalsColumn ropts =
875916 row_total_ ropts && balanceaccum_ ropts `notElem` [Cumulative , Historical ]
876917
877- multiBalanceRowAsText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
878- multiBalanceRowAsText opts =
918+ multiBalanceRowAsText ::
919+ ReportOpts -> [CommoditySymbol ] -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
920+ multiBalanceRowAsText opts allCommodities =
879921 rawTableContent .
880- multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts} opts []
922+ multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts}
923+ opts [] allCommodities
881924 Value simpleDateSpanCell
882925
883- multiBalanceRowAsCsvText :: ReportOpts -> [DateSpan ] -> PeriodicReportRow a MixedAmount -> [[T. Text ]]
884- multiBalanceRowAsCsvText opts colspans =
926+ multiBalanceRowAsCsvText ::
927+ ReportOpts -> [DateSpan ] -> [CommoditySymbol ] ->
928+ PeriodicReportRow a MixedAmount -> [[T. Text ]]
929+ multiBalanceRowAsCsvText opts colspans allCommodities =
885930 map (map (wbToText . Ods. cellContent)) .
886- multiBalanceRowAsCellBuilders machineFmt opts colspans
931+ multiBalanceRowAsCellBuilders machineFmt opts colspans allCommodities
887932 Value simpleDateSpanCell
888933
889934
0 commit comments