dev: clarify AmountDisplayOpts, add a new flag for symbol display

This commit is contained in:
Simon Michael 2023-12-07 14:25:40 -10:00
parent aa8c0e8279
commit 862b7e5712
5 changed files with 53 additions and 48 deletions

View File

@ -219,18 +219,19 @@ quoteCommoditySymbolIfNeeded s
-- | Options for the display of Amount and MixedAmount. -- | Options for the display of Amount and MixedAmount.
-- (ee also Types.AmountStyle. -- (ee also Types.AmountStyle.
data AmountDisplayOpts = AmountDisplayOpts data AmountDisplayOpts = AmountDisplayOpts
{ displayPrice :: Bool -- ^ Whether to display the Price of an Amount. { displayCommodity :: Bool -- ^ Whether to display commodity symbols.
, displayZeroCommodity :: Bool -- ^ If the Amount rounds to 0, whether to display its commodity string. , displayZeroCommodity :: Bool -- ^ Whether to display commodity symbols for zero Amounts.
, displayThousandsSep :: Bool -- ^ Whether to display digit group marks (eg thousands separators) , displayCommodityOrder :: Maybe [CommoditySymbol]
, displayAddDecimalMark :: Bool -- ^ Whether to add a trailing decimal mark when there are no decimal digits -- ^ For a MixedAmount, an optional order in which to display the commodities.
-- and there are digit group marks, to disambiguate -- Also causes 0s to be displayed for commodities which are not present.
, displayColour :: Bool -- ^ Whether to colourise negative Amounts. , displayDigitGroups :: Bool -- ^ Whether to display digit group marks (eg thousands separators)
, displayOneLine :: Bool -- ^ Whether to display on one line. , displayForceDecimalMark :: Bool -- ^ Whether to add a trailing decimal mark when there are no decimal digits
, displayMinWidth :: Maybe Int -- ^ Minimum width to pad to -- and there are digit group marks, to disambiguate
, displayMaxWidth :: Maybe Int -- ^ Maximum width to clip to , displayOneLine :: Bool -- ^ Whether to display on one line.
-- | Display amounts in this order (without the commodity symbol) and display , displayMinWidth :: Maybe Int -- ^ Minimum width to pad to
-- a 0 in case a corresponding commodity does not exist , displayMaxWidth :: Maybe Int -- ^ Maximum width to clip to
, displayOrder :: Maybe [CommoditySymbol] , displayCost :: Bool -- ^ Whether to display Amounts' costs.
, displayColour :: Bool -- ^ Whether to ansi-colourise negative Amounts.
} deriving (Show) } deriving (Show)
-- | By default, display Amount and MixedAmount using @noColour@ amount display options. -- | By default, display Amount and MixedAmount using @noColour@ amount display options.
@ -238,28 +239,30 @@ instance Default AmountDisplayOpts where def = noColour
-- | Display amounts without colour, and with various other defaults. -- | Display amounts without colour, and with various other defaults.
noColour :: AmountDisplayOpts noColour :: AmountDisplayOpts
noColour = AmountDisplayOpts { displayPrice = True noColour = AmountDisplayOpts {
, displayColour = False displayCommodity = True
, displayZeroCommodity = False , displayZeroCommodity = False
, displayThousandsSep = True , displayCommodityOrder = Nothing
, displayAddDecimalMark = False , displayDigitGroups = True
, displayOneLine = False , displayForceDecimalMark = False
, displayMinWidth = Just 0 , displayOneLine = False
, displayMaxWidth = Nothing , displayMinWidth = Just 0
, displayOrder = Nothing , displayMaxWidth = Nothing
} , displayCost = True
, displayColour = False
}
-- | Display Amount and MixedAmount with no prices. -- | Display Amount and MixedAmount with no prices.
noPrice :: AmountDisplayOpts noPrice :: AmountDisplayOpts
noPrice = def{displayPrice=False} noPrice = def{displayCost=False}
-- | Display Amount and MixedAmount on one line with no prices. -- | Display Amount and MixedAmount on one line with no prices.
oneLine :: AmountDisplayOpts oneLine :: AmountDisplayOpts
oneLine = def{displayOneLine=True, displayPrice=False} oneLine = def{displayOneLine=True, displayCost=False}
-- | Display Amount and MixedAmount in a form suitable for CSV output. -- | Display Amount and MixedAmount in a form suitable for CSV output.
csvDisplay :: AmountDisplayOpts csvDisplay :: AmountDisplayOpts
csvDisplay = oneLine{displayThousandsSep=False} csvDisplay = oneLine{displayDigitGroups=False}
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Amount arithmetic -- Amount arithmetic
@ -649,24 +652,26 @@ showAmount = wbUnpack . showAmountB noColour
showAmountB :: AmountDisplayOpts -> Amount -> WideBuilder showAmountB :: AmountDisplayOpts -> Amount -> WideBuilder
showAmountB _ Amount{acommodity="AUTO"} = mempty showAmountB _ Amount{acommodity="AUTO"} = mempty
showAmountB showAmountB
AmountDisplayOpts{displayPrice, displayColour, displayZeroCommodity, AmountDisplayOpts{displayCost, displayColour, displayZeroCommodity,
displayThousandsSep, displayAddDecimalMark, displayOrder} displayDigitGroups, displayForceDecimalMark, displayCommodityOrder}
a@Amount{astyle=style} = a@Amount{astyle=style} =
color $ case ascommodityside style of color $ case ascommodityside style of
L -> showC (wbFromText comm) space <> quantity' <> price L -> showsym (wbFromText comm) space <> quantity' <> price
R -> quantity' <> showC space (wbFromText comm) <> price R -> quantity' <> showsym space (wbFromText comm) <> price
where where
color = if displayColour && isNegativeAmount a then colorB Dull Red else id color = if displayColour && isNegativeAmount a then colorB Dull Red else id
quantity = showAmountQuantity displayAddDecimalMark $ quantity = showAmountQuantity displayForceDecimalMark $
if displayThousandsSep then a else a{astyle=(astyle a){asdigitgroups=Nothing}} if displayDigitGroups then a else a{astyle=(astyle a){asdigitgroups=Nothing}}
(quantity', comm) (quantity', comm)
| amountLooksZero a && not displayZeroCommodity = (WideBuilder (TB.singleton '0') 1, "") | amountLooksZero a && not displayZeroCommodity = (WideBuilder (TB.singleton '0') 1, "")
| otherwise = (quantity, quoteCommoditySymbolIfNeeded $ acommodity a) | otherwise = (quantity, quoteCommoditySymbolIfNeeded $ acommodity a)
space = if not (T.null comm) && ascommodityspaced style then WideBuilder (TB.singleton ' ') 1 else mempty space = if not (T.null comm) && ascommodityspaced style then WideBuilder (TB.singleton ' ') 1 else mempty
-- concatenate these texts, price = if displayCost then showAmountPrice a else mempty
-- or return the empty text if there's a commodity display order. XXX why ? -- Show a commodity symbol and its optional space, concatenated.
showC l r = if isJust displayOrder then mempty else l <> r -- Unless there's a commodity display order, in which case show nothing. XXX for --layout=bare, but wrong for --layout=tall
price = if displayPrice then showAmountPrice a else mempty showsym l r
| isJust displayCommodityOrder = mempty
| otherwise = l <> r
-- | Colour version. For a negative amount, adds ANSI codes to change the colour, -- | Colour version. For a negative amount, adds ANSI codes to change the colour,
-- currently to hard-coded red. -- currently to hard-coded red.
@ -1040,7 +1045,7 @@ showMixedAmount = wbUnpack . showMixedAmountB noColour
-- --
-- > showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine -- > showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine
showMixedAmountOneLine :: MixedAmount -> String showMixedAmountOneLine :: MixedAmount -> String
showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine{displayPrice=True} showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine{displayCost=True}
-- | Like showMixedAmount, but zero amounts are shown with their -- | Like showMixedAmount, but zero amounts are shown with their
-- commodity if they have one. -- commodity if they have one.
@ -1107,7 +1112,7 @@ showMixedAmountLinesB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidt
map (adBuilder . pad) elided map (adBuilder . pad) elided
where where
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . orderedAmounts opts $ astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . orderedAmounts opts $
if displayPrice opts then ma else mixedAmountStripPrices ma if displayCost opts then ma else mixedAmountStripPrices ma
sep = WideBuilder (TB.singleton '\n') 0 sep = WideBuilder (TB.singleton '\n') 0
width = maximum $ map (wbWidth . adBuilder) elided width = maximum $ map (wbWidth . adBuilder) elided
@ -1133,7 +1138,7 @@ showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWi
where where
width = maybe 0 adTotal $ lastMay elided width = maybe 0 adTotal $ lastMay elided
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . orderedAmounts opts $ astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . orderedAmounts opts $
if displayPrice opts then ma else mixedAmountStripPrices ma if displayCost opts then ma else mixedAmountStripPrices ma
sep = WideBuilder (TB.fromString ", ") 2 sep = WideBuilder (TB.fromString ", ") 2
n = length astrs n = length astrs
@ -1159,7 +1164,7 @@ showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWi
-- optionally preserving multiple zeros in different commodities, -- optionally preserving multiple zeros in different commodities,
-- optionally sorting them according to a commodity display order. -- optionally sorting them according to a commodity display order.
orderedAmounts :: AmountDisplayOpts -> MixedAmount -> [Amount] orderedAmounts :: AmountDisplayOpts -> MixedAmount -> [Amount]
orderedAmounts AmountDisplayOpts{displayZeroCommodity=preservezeros, displayOrder=mcommodityorder} = orderedAmounts AmountDisplayOpts{displayZeroCommodity=preservezeros, displayCommodityOrder=mcommodityorder} =
if preservezeros then amountsPreservingZeros else amounts if preservezeros then amountsPreservingZeros else amounts
<&> maybe id (mapM findfirst) mcommodityorder -- maybe sort them (somehow..) <&> maybe id (mapM findfirst) mcommodityorder -- maybe sort them (somehow..)
where where

View File

@ -293,7 +293,7 @@ postingAsLines elideamount onelineamounts acctwidth amtwidth p =
| elideamount = [mempty] | elideamount = [mempty]
| otherwise = showMixedAmountLinesB displayopts $ pamount p | otherwise = showMixedAmountLinesB displayopts $ pamount p
where displayopts = noColour{ where displayopts = noColour{
displayZeroCommodity=True, displayAddDecimalMark=True, displayOneLine=onelineamounts displayZeroCommodity=True, displayForceDecimalMark=True, displayOneLine=onelineamounts
} }
thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts
@ -361,7 +361,7 @@ postingAsLinesBeancount elideamount acctwidth amtwidth p =
| elideamount = [mempty] | elideamount = [mempty]
| otherwise = showMixedAmountLinesB displayopts a' | otherwise = showMixedAmountLinesB displayopts a'
where where
displayopts = noColour{ displayZeroCommodity=True, displayAddDecimalMark=True } displayopts = noColour{ displayZeroCommodity=True, displayForceDecimalMark=True }
a' = mapMixedAmount amountToBeancount $ pamount p a' = mapMixedAmount amountToBeancount $ pamount p
thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts

View File

@ -339,7 +339,7 @@ budgetReportAsTable
LayoutWide width -> LayoutWide width ->
( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=width} ( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=width}
, \a -> pure . percentage a) , \a -> pure . percentage a)
_ -> ( showMixedAmountLinesB noPrice{displayOrder=Just cs, displayMinWidth=Nothing, displayColour=color_} _ -> ( showMixedAmountLinesB noPrice{displayCommodityOrder=Just cs, displayMinWidth=Nothing, displayColour=color_}
, \a b -> fmap (percentage' a b) cs) , \a b -> fmap (percentage' a b) cs)
showrow :: [BudgetCell] -> [(WideBuilder, BudgetDisplayRow)] showrow :: [BudgetCell] -> [(WideBuilder, BudgetDisplayRow)]
@ -476,7 +476,7 @@ budgetReportAsCsv
| otherwise = | otherwise =
joinNames . zipWith (:) cs -- add symbols and names joinNames . zipWith (:) cs -- add symbols and names
. transpose -- each row becomes a list of Text quantities . transpose -- each row becomes a list of Text quantities
. fmap (fmap wbToText . showMixedAmountLinesB oneLine{displayOrder=Just cs, displayMinWidth=Nothing} . fmap (fmap wbToText . showMixedAmountLinesB oneLine{displayCommodityOrder=Just cs, displayMinWidth=Nothing}
.fromMaybe nullmixedamt) .fromMaybe nullmixedamt)
$ vals $ vals
where where

View File

@ -109,7 +109,7 @@ registerChartHtml q title percommoditytxnreports = $(hamletFile "templates/chart
colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex
commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)] commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)]
simpleMixedAmountQuantity = maybe 0 aquantity . listToMaybe . amounts . mixedAmountStripPrices simpleMixedAmountQuantity = maybe 0 aquantity . listToMaybe . amounts . mixedAmountStripPrices
showZeroCommodity = wbUnpack . showMixedAmountB oneLine{displayPrice=False,displayZeroCommodity=True} showZeroCommodity = wbUnpack . showMixedAmountB oneLine{displayCost=False,displayZeroCommodity=True}
shownull c = if null c then " " else c shownull c = if null c then " " else c
nodatelink = (RegisterR, [("q", T.unwords $ removeDates q)]) nodatelink = (RegisterR, [("q", T.unwords $ removeDates q)])

View File

@ -434,7 +434,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 = csvDisplay{displayOrder = order} where bopts = csvDisplay{displayCommodityOrder = order}
order = if layout_ opts == LayoutBare then Just (S.toList $ maCommodities amt) else Nothing order = if layout_ opts == LayoutBare then Just (S.toList $ maCommodities amt) else Nothing
-- | Render a single-column balance report as plain text. -- | Render a single-column balance report as plain text.
@ -467,7 +467,7 @@ balanceReportAsText' opts ((items, total)) =
[ Cell TopRight damts [ Cell TopRight damts
, 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 = oneLine{displayColour=color_ opts, displayOrder=Just cs} where dopts = oneLine{displayColour=color_ opts, displayCommodityOrder=Just cs}
cs = if mixedAmountLooksZero amt then [""] else S.toList $ maCommodities amt cs = if mixedAmountLooksZero amt then [""] else S.toList $ maCommodities amt
dispname = T.replicate ((dep - 1) * 2) " " <> acctname dispname = T.replicate ((dep - 1) * 2) " " <> acctname
damts = showMixedAmountLinesB dopts amt damts = showMixedAmountLinesB dopts amt
@ -737,12 +737,12 @@ multiBalanceRowAsWbs bopts ReportOpts{..} colspans (PeriodicReportRow _ as rowto
$ allamts $ allamts
LayoutBare -> zipWith (:) (fmap wbFromText cs) -- add symbols LayoutBare -> zipWith (:) (fmap wbFromText cs) -- add symbols
. transpose -- each row becomes a list of Text quantities . transpose -- each row becomes a list of Text quantities
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing}) . fmap (showMixedAmountLinesB bopts{displayCommodityOrder=Just cs, displayMinWidth=Nothing})
$ allamts $ allamts
LayoutTidy -> concat LayoutTidy -> concat
. zipWith (map . addDateColumns) colspans . zipWith (map . addDateColumns) colspans
. fmap ( zipWith (\c a -> [wbFromText c, a]) cs . fmap ( zipWith (\c a -> [wbFromText c, a]) cs
. showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing}) . showMixedAmountLinesB bopts{displayCommodityOrder=Just cs, displayMinWidth=Nothing})
$ as -- Do not include totals column or average for tidy output, as this $ as -- Do not include totals column or average for tidy output, as this
-- complicates the data representation and can be easily calculated -- complicates the data representation and can be easily calculated
where where