fix: bal: correctly handle empty commodity in commodity-column (#1654)
We can't filter out empty commodity strings since that is a legitimate group. Simultaneously, we should only include the empty commodity if it is explicitly used (part of a posting) and not generated as part of `Amounts.amounts`
This commit is contained in:
		
							parent
							
								
									07eb3a9086
								
							
						
					
					
						commit
						44e1ea10fa
					
				| @ -100,6 +100,7 @@ module Hledger.Data.Amount ( | |||||||
|   maAddAmounts, |   maAddAmounts, | ||||||
|   amounts, |   amounts, | ||||||
|   amountsRaw, |   amountsRaw, | ||||||
|  |   maCommodities, | ||||||
|   filterMixedAmount, |   filterMixedAmount, | ||||||
|   filterMixedAmountByCommodity, |   filterMixedAmountByCommodity, | ||||||
|   mapMixedAmount, |   mapMixedAmount, | ||||||
| @ -152,6 +153,7 @@ import Data.Foldable (toList) | |||||||
| import Data.List (find, foldl', intercalate, intersperse, mapAccumL, partition) | import Data.List (find, foldl', intercalate, intersperse, mapAccumL, partition) | ||||||
| import Data.List.NonEmpty (NonEmpty(..), nonEmpty) | import Data.List.NonEmpty (NonEmpty(..), nonEmpty) | ||||||
| import qualified Data.Map.Strict as M | import qualified Data.Map.Strict as M | ||||||
|  | import qualified Data.Set as S | ||||||
| import Data.Maybe (fromMaybe, isNothing, isJust) | import Data.Maybe (fromMaybe, isNothing, isJust) | ||||||
| import Data.Semigroup (Semigroup(..)) | import Data.Semigroup (Semigroup(..)) | ||||||
| import qualified Data.Text as T | import qualified Data.Text as T | ||||||
| @ -662,6 +664,11 @@ amounts (Mixed ma) | |||||||
| amountsRaw :: MixedAmount -> [Amount] | amountsRaw :: MixedAmount -> [Amount] | ||||||
| amountsRaw (Mixed ma) = toList ma | amountsRaw (Mixed ma) = toList ma | ||||||
| 
 | 
 | ||||||
|  | -- | Get the set of mixed amount commodities. Returns an empty set of no amounts | ||||||
|  | maCommodities :: MixedAmount -> S.Set CommoditySymbol | ||||||
|  | maCommodities = S.fromList . fmap acommodity . amounts' | ||||||
|  |   where amounts' ma@(Mixed m) = if M.null m then [] else amounts ma | ||||||
|  | 
 | ||||||
| normaliseMixedAmount :: MixedAmount -> MixedAmount | normaliseMixedAmount :: MixedAmount -> MixedAmount | ||||||
| normaliseMixedAmount = id  -- XXX Remove | normaliseMixedAmount = id  -- XXX Remove | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -241,12 +241,12 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ | |||||||
|           ( textCell TopLeft rh |           ( textCell TopLeft rh | ||||||
|           , textsCell TopLeft cs : fmap (uncurry (showcell' cs)) cells) |           , textsCell TopLeft cs : fmap (uncurry (showcell' cs)) cells) | ||||||
|       where |       where | ||||||
|         cs = filter (not . T.null) . S.toList . foldl' S.union mempty |         cs = S.toList . foldl' S.union mempty | ||||||
|             . fmap (budgetCellCommodities . fst . snd) $ cells |             . fmap (budgetCellCommodities . fst . snd) $ cells | ||||||
| 
 | 
 | ||||||
|     budgetCellCommodities :: BudgetCell -> S.Set CommoditySymbol |     budgetCellCommodities :: BudgetCell -> S.Set CommoditySymbol | ||||||
|     budgetCellCommodities (am, bm) = f am `S.union` f bm |     budgetCellCommodities (am, bm) = f am `S.union` f bm | ||||||
|       where f = S.fromList . fmap acommodity . amounts . fromMaybe nullmixedamt |       where f = maybe mempty maCommodities | ||||||
| 
 | 
 | ||||||
|     displayTableWithWidths :: Table Text Text ((Int, Int, Int), BudgetDisplayCell) |     displayTableWithWidths :: Table Text Text ((Int, Int, Int), BudgetDisplayCell) | ||||||
|     displayTableWithWidths = Table rh ch $ map (zipWith (,) widths) displaycells |     displayTableWithWidths = Table rh ch $ map (zipWith (,) widths) displaycells | ||||||
| @ -436,10 +436,7 @@ budgetReportAsCsv | |||||||
|           . fmap (fromMaybe nullmixedamt) |           . fmap (fromMaybe nullmixedamt) | ||||||
|           $ all |           $ all | ||||||
|       where |       where | ||||||
|         cs = commodities $ catMaybes all |         cs = S.toList . foldl' S.union mempty . fmap maCommodities $ catMaybes all | ||||||
|         commodities = filter (not . T.null) . S.toList |  | ||||||
|             . foldl' S.union mempty |  | ||||||
|             . fmap (S.fromList . fmap acommodity . amounts) |  | ||||||
|         all = flattentuples as |         all = flattentuples as | ||||||
|             ++ concat [[rowtot, budgettot] | row_total_] |             ++ concat [[rowtot, budgettot] | row_total_] | ||||||
|             ++ concat [[rowavg, budgetavg] | average_] |             ++ concat [[rowavg, budgetavg] | average_] | ||||||
|  | |||||||
| @ -408,7 +408,7 @@ balanceReportAsCsv opts (items, total) = | |||||||
|     showName = accountNameDrop (drop_ opts) |     showName = accountNameDrop (drop_ opts) | ||||||
|     renderAmount amt = wbToText $ showMixedAmountB bopts amt |     renderAmount amt = wbToText $ showMixedAmountB bopts amt | ||||||
|       where bopts = (balanceOpts False opts){displayOrder = order} |       where bopts = (balanceOpts False opts){displayOrder = order} | ||||||
|             order = if commodity_column_ opts then Just (commodities [amt]) else Nothing |             order = if commodity_column_ opts then Just (S.toList $ maCommodities amt) else Nothing | ||||||
|     sumAmounts mp am = M.insertWith (+) (acommodity am) am mp |     sumAmounts mp am = M.insertWith (+) (acommodity am) am mp | ||||||
| 
 | 
 | ||||||
| -- | Render a single-column balance report as plain text. | -- | Render a single-column balance report as plain text. | ||||||
| @ -444,7 +444,7 @@ balanceReportAsText' opts ((items, total)) = | |||||||
|         , Cell TopLeft (fmap wbFromText cs) |         , Cell TopLeft (fmap wbFromText cs) | ||||||
|         , Cell TopLeft (replicate (length damts - 1) mempty ++ [wbFromText dispname]) ] |         , Cell TopLeft (replicate (length damts - 1) mempty ++ [wbFromText dispname]) ] | ||||||
|       where dopts = (balanceOpts True opts){displayOrder=Just cs} |       where dopts = (balanceOpts True opts){displayOrder=Just cs} | ||||||
|             cs    = commodities [amt] |             cs    = S.toList $ maCommodities amt | ||||||
|             dispname = T.replicate ((depth - 1) * 2) " " <> acctname |             dispname = T.replicate ((depth - 1) * 2) " " <> acctname | ||||||
|             damts = showMixedAmountLinesB dopts amt |             damts = showMixedAmountLinesB dopts amt | ||||||
|     lines = fmap render items |     lines = fmap render items | ||||||
| @ -528,7 +528,7 @@ multiBalanceReportAsCsv' opts@ReportOpts{..} | |||||||
|           $ all |           $ all | ||||||
|       where |       where | ||||||
|         bopts = balanceOpts False opts |         bopts = balanceOpts False opts | ||||||
|         cs = commodities $ rowtot : rowavg : as |         cs = S.toList . foldl' S.union mempty $ fmap maCommodities $ rowtot : rowavg : as | ||||||
|         all = as |         all = as | ||||||
|             ++ [rowtot | row_total_] |             ++ [rowtot | row_total_] | ||||||
|             ++ [rowavg | average_] |             ++ [rowavg | average_] | ||||||
| @ -717,12 +717,7 @@ balanceReportTableAsText ropts@ReportOpts{..} = | |||||||
|             : fmap (Cell TopRight . showMixedAmountLinesB bopts{displayOrder = Just cs}) row) |             : fmap (Cell TopRight . showMixedAmountLinesB bopts{displayOrder = Just cs}) row) | ||||||
|       where |       where | ||||||
|         bopts = balanceOpts True ropts |         bopts = balanceOpts True ropts | ||||||
|         cs = commodities row |         cs = S.toList . foldl' S.union mempty $ fmap maCommodities row | ||||||
| 
 |  | ||||||
| commodities :: [MixedAmount] -> [CommoditySymbol] |  | ||||||
| commodities = filter (not . T.null) . S.toList |  | ||||||
|     . foldl' S.union mempty |  | ||||||
|     . fmap (S.fromList . fmap acommodity . amounts) |  | ||||||
| 
 | 
 | ||||||
| -- | Amount display options to use for balance reports | -- | Amount display options to use for balance reports | ||||||
| balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts | balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user