lib,cli: Remove showAmounts*B functions, replacing them entirely with showMixedAmount*B functions.

This commit is contained in:
Stephen Morgan 2021-04-12 22:50:56 +10:00 committed by Simon Michael
parent 5e7b69356f
commit 4780a02e5a
4 changed files with 76 additions and 95 deletions

View File

@ -77,8 +77,6 @@ module Hledger.Data.Amount (
styleAmountExceptPrecision,
amountUnstyled,
showAmountB,
showAmountsB,
showAmountsLinesB,
showAmount,
cshowAmount,
showAmountWithZeroCommodity,
@ -136,6 +134,7 @@ module Hledger.Data.Amount (
showMixedAmountElided,
showMixedAmountWithZeroCommodity,
showMixedAmountB,
showMixedAmountLinesB,
wbToText,
wbUnpack,
mixedAmountSetPrecision,
@ -441,82 +440,6 @@ showAmountB opts a@Amount{astyle=style} =
price = if displayPrice opts then showAmountPrice a else mempty
color = if displayColour opts && isNegativeAmount a then colorB Dull Red else id
-- | General function to generate a WideBuilder for a list of Amounts, according the
-- supplied AmountDisplayOpts. This is the main function to use for showing
-- a list of Amounts, constructing a builder; it can then be converted to a Text with
-- wbToText, or to a String with wbUnpack.
--
-- The list of Amounts is not normalised, and will be displayed as-is.
--
-- If a maximum width is given then:
-- - If displayed on one line, it will display as many Amounts as can
-- fit in the given width, and further Amounts will be elided. There
-- will always be at least one amount displayed, even if this will
-- exceed the requested maximum width.
-- - If displayed on multiple lines, any Amounts longer than the
-- maximum width will be elided.
showAmountsB :: AmountDisplayOpts -> [Amount] -> WideBuilder
showAmountsB opts amts'
| displayOneLine opts = showAmountsOneLineB opts amts
| otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width
where
amts = if null amts' then [nullamt] else amts'
lines = showAmountsLinesB opts amts
width = headDef 0 $ map wbWidth lines
sep = WideBuilder (TB.singleton '\n') 0
-- | Helper for showAmountsB to show a list of Amounts on multiple lines. This returns
-- the list of WideBuilders: one for each Amount, and padded/elided to the appropriate
-- width. This does not honour displayOneLine: all amounts will be displayed as if
-- displayOneLine were False.
showAmountsLinesB :: AmountDisplayOpts -> [Amount] -> [WideBuilder]
showAmountsLinesB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} amts =
map (adBuilder . pad) elided
where
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) amts
sep = WideBuilder (TB.singleton '\n') 0
width = maximum $ fromMaybe 0 mmin : map (wbWidth . adBuilder) elided
pad amt = amt{ adBuilder = WideBuilder (TB.fromText $ T.replicate w " ") w <> adBuilder amt }
where w = width - wbWidth (adBuilder amt)
elided = maybe id elideTo mmax astrs
elideTo m xs = maybeAppend elisionStr short
where
elisionStr = elisionDisplay (Just m) (wbWidth sep) (length long) $ lastDef nullAmountDisplay short
(short, long) = partition ((m>=) . wbWidth . adBuilder) xs
-- | Helper for showAmountsB to deal with single line displays. This does not
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
-- were True.
showAmountsOneLineB :: AmountDisplayOpts -> [Amount] -> WideBuilder
showAmountsOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} amts =
WideBuilder (wbBuilder . pad . mconcat . intersperse sep $ map adBuilder elided)
. max width $ fromMaybe 0 mmin
where
width = maybe 0 adTotal $ lastMay elided
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) amts
sep = WideBuilder (TB.fromString ", ") 2
n = length amts
pad = (WideBuilder (TB.fromText $ T.replicate w " ") w <>)
where w = fromMaybe 0 mmin - width
elided = maybe id elideTo mmax astrs
elideTo m = addElide . takeFitting m . withElided
-- Add the last elision string to the end of the display list
addElide [] = []
addElide xs = maybeAppend (snd $ last xs) $ map fst xs
-- Return the elements of the display list which fit within the maximum width
-- (including their elision strings). Always display at least one amount,
-- regardless of width.
takeFitting _ [] = []
takeFitting m (x:xs) = x : dropWhileRev (\(a,e) -> m < adTotal (fromMaybe a e)) xs
dropWhileRev p = foldr (\x xs -> if null xs && p x then [] else x:xs) []
-- Add the elision strings (if any) to each amount
withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing (wbWidth sep) num amt)) [n-1,n-2..0]
-- | Colour version. For a negative amount, adds ANSI codes to change the colour,
-- currently to hard-coded red.
--
@ -873,17 +796,75 @@ showMixedAmountDebug m | m == missingmixedamt = "(missing)"
-- MixedAmounts, constructing a builder; it can then be converted to a Text with
-- wbToText, or to a String with wbUnpack.
--
-- This normalises the MixedAmount before displaying: if you don't want this,
-- use showAmountsB.
--
-- If a maximum width is given then:
-- - If displayed on one line, it will display as many Amounts as can
-- fit in the given width, and further Amounts will be elided.
-- fit in the given width, and further Amounts will be elided. There
-- will always be at least one amount displayed, even if this will
-- exceed the requested maximum width.
-- - If displayed on multiple lines, any Amounts longer than the
-- maximum width will be elided.
showMixedAmountB :: AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB opts =
showAmountsB opts . amounts . if displayPrice opts then id else mixedAmountStripPrices
showMixedAmountB opts ma
| displayOneLine opts = showMixedAmountOneLineB opts ma
| otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width
where
lines = showMixedAmountLinesB opts ma
width = headDef 0 $ map wbWidth lines
sep = WideBuilder (TB.singleton '\n') 0
-- | Helper for showMixedAmountB to show a list of Amounts on multiple lines. This returns
-- the list of WideBuilders: one for each Amount, and padded/elided to the appropriate
-- width. This does not honour displayOneLine: all amounts will be displayed as if
-- displayOneLine were False.
showMixedAmountLinesB :: AmountDisplayOpts -> MixedAmount -> [WideBuilder]
showMixedAmountLinesB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
map (adBuilder . pad) elided
where
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . amounts $
if displayPrice opts then ma else mixedAmountStripPrices ma
sep = WideBuilder (TB.singleton '\n') 0
width = maximum $ fromMaybe 0 mmin : map (wbWidth . adBuilder) elided
pad amt = amt{ adBuilder = WideBuilder (TB.fromText $ T.replicate w " ") w <> adBuilder amt }
where w = width - wbWidth (adBuilder amt)
elided = maybe id elideTo mmax astrs
elideTo m xs = maybeAppend elisionStr short
where
elisionStr = elisionDisplay (Just m) (wbWidth sep) (length long) $ lastDef nullAmountDisplay short
(short, long) = partition ((m>=) . wbWidth . adBuilder) xs
-- | Helper for showMixedAmountB to deal with single line displays. This does not
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
-- were True.
showMixedAmountOneLineB :: AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
WideBuilder (wbBuilder . pad . mconcat . intersperse sep $ map adBuilder elided)
. max width $ fromMaybe 0 mmin
where
width = maybe 0 adTotal $ lastMay elided
astrs = amtDisplayList (wbWidth sep) (showAmountB opts) . amounts $
if displayPrice opts then ma else mixedAmountStripPrices ma
sep = WideBuilder (TB.fromString ", ") 2
n = length astrs
pad = (WideBuilder (TB.fromText $ T.replicate w " ") w <>)
where w = fromMaybe 0 mmin - width
elided = maybe id elideTo mmax astrs
elideTo m = addElide . takeFitting m . withElided
-- Add the last elision string to the end of the display list
addElide [] = []
addElide xs = maybeAppend (snd $ last xs) $ map fst xs
-- Return the elements of the display list which fit within the maximum width
-- (including their elision strings). Always display at least one amount,
-- regardless of width.
takeFitting _ [] = []
takeFitting m (x:xs) = x : dropWhileRev (\(a,e) -> m < adTotal (fromMaybe a e)) xs
dropWhileRev p = foldr (\x xs -> if null xs && p x then [] else x:xs) []
-- Add the elision strings (if any) to each amount
withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing (wbWidth sep) num amt)) [n-1,n-2..0]
data AmountDisplay = AmountDisplay
{ adBuilder :: !WideBuilder -- ^ String representation of the Amount

View File

@ -284,7 +284,7 @@ postingAsLines elideamount onelineamounts acctwidth amtwidth p =
-- amtwidth at all.
shownAmounts
| elideamount = [mempty]
| otherwise = showAmountsLinesB noColour{displayOneLine=onelineamounts} . amounts $ pamount p
| otherwise = showMixedAmountLinesB noColour{displayOneLine=onelineamounts} $ pamount p
thisamtwidth = maximumDef 0 $ map wbWidth shownAmounts
(samelinecomment, newlinecomments) =

View File

@ -336,7 +336,7 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
where
sameamount (p1,p2) = mixedAmountUnstyled (pamount p1) == mixedAmountUnstyled (pamount p2)
def | (d:_) <- esArgs = d
| Just hp <- mhistoricalp, followedhistoricalsofar = showamt . amounts $ pamount hp
| Just hp <- mhistoricalp, followedhistoricalsofar = showamt $ pamount hp
| pnum > 1 && not (mixedAmountLooksZero balancingamt) = showamt balancingamtfirstcommodity
| otherwise = ""
retryMsg "A valid hledger amount is required. Eg: 1, $2, 3 EUR, \"4 red apples\"." $
@ -360,8 +360,8 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
-- eof
return (a,c)
balancingamt = maNegate . sumPostings $ filter isReal esPostings
balancingamtfirstcommodity = take 1 $ amounts balancingamt
showamt = wbUnpack . showAmountsB noColour . map (amountSetPrecision
balancingamtfirstcommodity = mixed . take 1 $ amounts balancingamt
showamt = wbUnpack . showMixedAmountB noColour . mixedAmountSetPrecision
-- what should this be ?
-- 1 maxprecision (show all decimal places or none) ?
-- 2 maxprecisionwithpoint (show all decimal places or .0 - avoids some but not all confusion with thousands separators) ?
@ -369,7 +369,7 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
-- 4 maximum precision entered so far in this transaction ?
-- 5 3 or 4, whichever would show the most decimal places ?
-- I think 1 or 4, whichever would show the most decimal places
NaturalPrecision)
NaturalPrecision
--
-- let -- (amt,comment) = (strip a, strip $ dropWhile (==';') b) where (a,b) = break (==';') amtcmt
-- a = fromparse $ runParser (amountp <|> return missingamt) (jparsestate esJournal) "" amt

View File

@ -109,9 +109,9 @@ postingsReportAsText opts items = TB.toLazyText $ foldMap first3 linesWithWidths
amtwidth = maximumStrict $ 12 : widths (map itemamt items)
balwidth = maximumStrict $ 12 : widths (map itembal items)
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
widths = map wbWidth . concatMap (showAmountsLinesB oneLine{displayPrice=True})
itemamt (_,_,_,Posting{pamount=a},_) = amounts a
itembal (_,_,_,_,a) = amounts a
widths = map wbWidth . concatMap (showMixedAmountLinesB oneLine{displayPrice=True})
itemamt (_,_,_,Posting{pamount=a},_) = a
itembal (_,_,_,_,a) = a
-- | Render one register report line item as plain text. Layout is like so:
-- @
@ -190,10 +190,10 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
BalancedVirtualPosting -> (wrap "[" "]", acctwidth-2)
VirtualPosting -> (wrap "(" ")", acctwidth-2)
_ -> (id,acctwidth)
amt = showAmountsLinesB dopts . (\x -> if null x then [nullamt] else x) . amountsRaw $ pamount p
bal = showAmountsLinesB dopts $ amounts b
amt = showamt $ pamount p
bal = showamt b
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
dopts = oneLine{displayColour=color_, displayPrice=True}
showamt = showMixedAmountLinesB oneLine{displayColour=color_, displayPrice=True}
where ReportOpts{..} = rsOpts $ reportspec_ opts
-- Since this will usually be called with the knot tied between this(amt|bal)width and
-- preferred(amt|bal)width, make sure the former do not depend on the latter to avoid loops.