@@ -583,15 +583,8 @@ renderComponent topaligned oneline opts (acctname, dep, total) (FormatField ljus
583583 }
584584
585585
586- headerCell :: Text -> Ods. Cell Ods. NumLines Text
587- headerCell text =
588- let deflt = Ods. defaultCell text
589- in
590- deflt {
591- Ods. cellStyle = Ods. Head ,
592- Ods. cellBorder =
593- (Ods. cellBorder deflt) {Ods. borderBottom = Ods. DoubleLine }
594- }
586+ headerCell :: (Ods. Lines borders ) => Text -> Ods. Cell borders Text
587+ headerCell text = (Ods. defaultCell text) {Ods. cellStyle = Ods. Head }
595588
596589registerQueryUrl :: [Text ] -> Text
597590registerQueryUrl query =
@@ -633,13 +626,30 @@ replaceDate :: Text -> [Text] -> [Text]
633626replaceDate prd query = " date:" <> prd : removeDates query
634627
635628headerDateSpanCell ::
636- Maybe Text -> [Text ] -> DateSpan -> Ods. Cell Ods. NumLines Text
629+ Maybe Text -> [Text ] -> DateSpan -> Ods. Cell () Text
637630headerDateSpanCell base query spn =
638631 let prd = showDateSpan spn in
639632 (headerCell prd) {
640633 Ods. cellAnchor = composeAnchor base $ replaceDate prd query
641634 }
642635
636+ headerWithoutBorders :: [Ods. Cell () text ] -> [Ods. Cell Ods. NumLines text ]
637+ headerWithoutBorders = map (\ c -> c {Ods. cellBorder = Ods. noBorder})
638+
639+ addHeaderBorders :: [Ods. Cell () text ] -> [Ods. Cell Ods. NumLines text ]
640+ addHeaderBorders =
641+ map (\ c -> c {Ods. cellBorder =
642+ Ods. noBorder {Ods. borderBottom = Ods. DoubleLine }})
643+
644+ groupHeaderCells ::
645+ (Ods. Lines border , Monoid text ) =>
646+ [a ] -> Ods. Cell border text -> [Ods. Cell border text ]
647+ groupHeaderCells subCells cell =
648+ zipWith const
649+ (cell{Ods. cellSpan = Ods. SpanHorizontal $ length subCells}
650+ : repeat (Ods. emptyCell {Ods. cellSpan = Ods. Covered }))
651+ subCells
652+
643653simpleDateSpanCell :: DateSpan -> Ods. Cell Ods. NumLines Text
644654simpleDateSpanCell = Ods. defaultCell . showDateSpan
645655
@@ -697,10 +707,13 @@ balanceReportAsSpreadsheet opts (items, total) =
697707 where
698708 cell = Ods. defaultCell
699709 headers =
700- map headerCell $
710+ addHeaderBorders $ map headerCell $
701711 " account" : case layout_ opts of
712+ LayoutBareWide -> allCommodities
702713 LayoutBare -> [" commodity" , " balance" ]
703714 _ -> [" balance" ]
715+ allCommodities =
716+ S. toAscList $ foldMap (\ (_,_,_,ma) -> maCommodities ma) items
704717 rows ::
705718 RowClass -> BalanceReportItem ->
706719 [[Ods. Cell Ods. NumLines Text ]]
@@ -712,6 +725,15 @@ balanceReportAsSpreadsheet opts (items, total) =
712725 cell $ renderBalanceAcct opts nbsp (name, dispName, dep) in
713726 addRowSpanHeader accountCell $
714727 case layout_ opts of
728+ LayoutBareWide ->
729+ let bopts =
730+ machineFmt {
731+ displayCommodity = False ,
732+ displayCommodityOrder = Just allCommodities
733+ } in
734+ [map (\ bldAmt ->
735+ fmap wbToText $ cellFromAmount bopts (amountClass rc, bldAmt)) $
736+ showMixedAmountLinesPartsB bopts ma]
715737 LayoutBare ->
716738 map (\ a -> [cell $ acommodity a, renderAmount rc $ mixedAmount a])
717739 . amounts $ mixedAmountStripCosts ma
@@ -749,6 +771,15 @@ cellsFromMixedAmount bopts (cls, mixedAmt) =
749771 })
750772 (showMixedAmountLinesPartsB bopts mixedAmt)
751773
774+ cellFromAmount ::
775+ (Ods. Lines border ) =>
776+ AmountFormat -> (Ods. Class , (wb , Amount )) -> Ods. Cell border wb
777+ cellFromAmount bopts (cls, (str,amt)) =
778+ (Ods. defaultCell str) {
779+ Ods. cellClass = cls,
780+ Ods. cellType = amountType bopts amt
781+ }
782+
752783amountType :: AmountFormat -> Amount -> Ods. Type
753784amountType bopts amt =
754785 Ods. TypeAmount $
@@ -771,30 +802,43 @@ multiBalanceReportAsCsv opts@ReportOpts{..} report = maybeTranspose allRows
771802 case layout_ of
772803 LayoutTidy -> rows -- tidy csv should not include totals or averages
773804 _ -> rows ++ totals
774- rows = header: body
805+ rows = header++ body
775806 (header, body, totals) =
776- multiBalanceReportAsSpreadsheetParts machineFmt opts report
807+ multiBalanceReportAsSpreadsheetParts machineFmt opts
808+ (allCommoditiesFromPeriodicReport $ prRows report) report
777809 maybeTranspose = if transpose_ then transpose else id
778810
779811-- | Render the Spreadsheet table rows (CSV, ODS, HTML) for a MultiBalanceReport.
780812-- Returns the heading row, 0 or more body rows, and the totals row if enabled.
781813multiBalanceReportAsSpreadsheetParts ::
782- AmountFormat -> ReportOpts -> MultiBalanceReport ->
783- ([Ods. Cell Ods. NumLines Text ],
814+ AmountFormat -> ReportOpts ->
815+ [CommoditySymbol ] -> MultiBalanceReport ->
816+ ([[Ods. Cell Ods. NumLines Text ]],
784817 [[Ods. Cell Ods. NumLines Text ]],
785818 [[Ods. Cell Ods. NumLines Text ]])
786- multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. } (PeriodicReport colspans items tr) =
787- (headers, concatMap fullRowAsTexts items, addTotalBorders totalrows)
819+ multiBalanceReportAsSpreadsheetParts fmt opts@ ReportOpts {.. }
820+ allCommodities (PeriodicReport colspans items tr) =
821+ (allHeaders, concatMap fullRowAsTexts items, addTotalBorders totalrows)
788822 where
789823 accountCell label =
790824 (Ods. defaultCell label) {Ods. cellClass = Ods. Class " account" }
791825 hCell cls label = (headerCell label) {Ods. cellClass = Ods. Class cls}
826+ allHeaders =
827+ case layout_ of
828+ LayoutBareWide ->
829+ [headerWithoutBorders $
830+ Ods. emptyCell :
831+ concatMap (groupHeaderCells allCommodities) dateHeaders,
832+ headers]
833+ _ -> [headers]
792834 headers =
835+ addHeaderBorders $
793836 hCell " account" " account" :
794837 case layout_ of
795838 LayoutTidy ->
796839 map headerCell
797840 [" period" , " start_date" , " end_date" , " commodity" , " value" ]
841+ LayoutBareWide -> dateHeaders >> map headerCell allCommodities
798842 LayoutBare -> headerCell " commodity" : dateHeaders
799843 _ -> dateHeaders
800844 dateHeaders =
@@ -815,7 +859,7 @@ multiBalanceReportAsSpreadsheetParts fmt opts@ReportOpts{..} (PeriodicReport col
815859 rowAsText Total simpleDateSpanCell tr
816860 rowAsText rc dsCell =
817861 map (map (fmap wbToText)) .
818- multiBalanceRowAsCellBuilders fmt opts colspans rc dsCell
862+ multiBalanceRowAsCellBuilders fmt opts colspans allCommodities rc dsCell
819863
820864
821865-- | Render a multi-column balance report as HTML.
@@ -833,10 +877,12 @@ multiBalanceReportAsSpreadsheet ::
833877 ((Maybe Int , Maybe Int ), [[Ods. Cell Ods. NumLines Text ]])
834878multiBalanceReportAsSpreadsheet ropts mbr =
835879 let (header,body,total) =
836- multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts mbr
880+ multiBalanceReportAsSpreadsheetParts oneLineNoCostFmt ropts
881+ (allCommoditiesFromPeriodicReport $ prRows mbr) mbr
837882 in (if transpose_ ropts then swap *** Ods. transpose else id ) $
838- ((Just 1 , case layout_ ropts of LayoutWide _ -> Just 1 ; _ -> Nothing ),
839- header : body ++ total)
883+ ((Just $ case layout_ ropts of LayoutBareWide -> 2 ; _ -> 1 ,
884+ case layout_ ropts of LayoutWide _ -> Just 1 ; _ -> Nothing ),
885+ header ++ body ++ total)
840886
841887
842888-- | Render a multi-column balance report as plain text suitable for console output.
@@ -908,19 +954,24 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, row_total_, b
908954 where
909955 totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative , Historical ]
910956 colheadings = [" Commodity" | layout_ opts == LayoutBare ]
911- ++ (if not summary_only_ then map (reportPeriodName balanceaccum_ spans) spans else [] )
957+ ++ (if not summary_only_
958+ then case layout_ opts of
959+ LayoutBareWide -> spans >> allCommodities
960+ _ -> map (reportPeriodName balanceaccum_ spans) spans
961+ else [] )
912962 ++ [" Total" | totalscolumn]
913963 ++ [" Average" | average_]
964+ allCommodities = allCommoditiesFromPeriodicReport items
914965 (accts, rows) = unzip $ fmap fullRowAsTexts items
915966 where
916967 fullRowAsTexts row = (replicate (length rs) (renderacct row), rs)
917968 where
918- rs = multiBalanceRowAsText opts row
969+ rs = multiBalanceRowAsText opts allCommodities row
919970 renderacct row' = T. replicate (prrIndent row' * 2 ) " " <> prrDisplayName row'
920971 addtotalrow
921972 | no_total_ opts = id
922973 | otherwise =
923- let totalrows = multiBalanceRowAsText opts tr
974+ let totalrows = multiBalanceRowAsText opts allCommodities tr
924975 rowhdrs = Group NoLine $ map Header $ totalRowHeadingText : replicate (length totalrows - 1 ) " "
925976 colhdrs = Header [] -- unused, concatTables will discard
926977 in (flip (concatTables SingleLine ) $ Table rowhdrs colhdrs totalrows)
@@ -929,12 +980,17 @@ multiBalanceReportAsTable opts@ReportOpts{summary_only_, average_, row_total_, b
929980 multiColumnTableInterRowBorder = NoLine
930981 multiColumnTableInterColumnBorder = if pretty_ opts then SingleLine else NoLine
931982
983+ allCommoditiesFromPeriodicReport ::
984+ [PeriodicReportRow a MixedAmount ] -> [CommoditySymbol ]
985+ allCommoditiesFromPeriodicReport =
986+ S. toAscList . foldMap (foldMap maCommodities . prrAmounts)
987+
932988multiBalanceRowAsCellBuilders ::
933- AmountFormat -> ReportOpts -> [DateSpan ] ->
989+ AmountFormat -> ReportOpts -> [DateSpan ] -> [ CommoditySymbol ] ->
934990 RowClass -> (DateSpan -> Ods. Cell Ods. NumLines Text ) ->
935991 PeriodicReportRow a MixedAmount ->
936992 [[Ods. Cell Ods. NumLines WideBuilder ]]
937- multiBalanceRowAsCellBuilders bopts ReportOpts {.. } colspans
993+ multiBalanceRowAsCellBuilders bopts ReportOpts {.. } colspans allCommodities
938994 rc renderDateSpanCell (PeriodicReportRow _acct as rowtot rowavg) =
939995 case layout_ of
940996 LayoutWide width -> [fmap (cellFromMixedAmount bopts{displayMaxWidth= width}) clsamts]
@@ -945,6 +1001,8 @@ multiBalanceRowAsCellBuilders bopts ReportOpts{..} colspans
9451001 . transpose -- each row becomes a list of Text quantities
9461002 . map (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just cs, displayMinWidth= Nothing })
9471003 $ clsamts
1004+ LayoutBareWide -> [concatMap (cellsFromMixedAmount bopts{displayCommodity= False , displayCommodityOrder= Just allCommodities, displayMinWidth= Nothing })
1005+ $ clsamts]
9481006 LayoutTidy -> concat
9491007 . zipWith (map . addDateColumns) colspans
9501008 . map ( zipWith (\ c a -> [wbCell c, a]) cs
@@ -983,16 +1041,20 @@ multiBalanceRowAsCellBuilders bopts ReportOpts{..} colspans
9831041 m [] = [n]
9841042
9851043
986- multiBalanceRowAsText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
987- multiBalanceRowAsText opts =
1044+ multiBalanceRowAsText ::
1045+ ReportOpts -> [CommoditySymbol ] -> PeriodicReportRow a MixedAmount -> [[WideBuilder ]]
1046+ multiBalanceRowAsText opts allCommodities =
9881047 rawTableContent .
989- multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts} opts []
1048+ multiBalanceRowAsCellBuilders oneLineNoCostFmt{displayColour= color_ opts}
1049+ opts [] allCommodities
9901050 Value simpleDateSpanCell
9911051
992- multiBalanceRowAsCsvText :: ReportOpts -> [DateSpan ] -> PeriodicReportRow a MixedAmount -> [[T. Text ]]
993- multiBalanceRowAsCsvText opts colspans =
1052+ multiBalanceRowAsCsvText ::
1053+ ReportOpts -> [DateSpan ] -> [CommoditySymbol ] ->
1054+ PeriodicReportRow a MixedAmount -> [[T. Text ]]
1055+ multiBalanceRowAsCsvText opts colspans allCommodities =
9941056 map (map (wbToText . Ods. cellContent)) .
995- multiBalanceRowAsCellBuilders machineFmt opts colspans
1057+ multiBalanceRowAsCellBuilders machineFmt opts colspans allCommodities
9961058 Value simpleDateSpanCell
9971059
9981060
@@ -1254,7 +1316,7 @@ budgetReportAsSpreadsheet
12541316 = (if transpose_ then Ods. transpose else id ) $
12551317
12561318 -- heading row
1257- (map headerCell $
1319+ (addHeaderBorders $ map headerCell $
12581320 " Account" :
12591321 [" Commodity" | layout_ == LayoutBare ]
12601322 ++ concatMap (\ spn -> [showDateSpan spn, " budget" ]) colspans
0 commit comments