lib: Split showMixedAmountB into showMixedAmountB and showAmountsB, the

former being a simple wrapper around the latter.

This removes the need for the showNormalised option, as showMixedAmountB
will always showNormalised and showAmountsB will never do so.

We also strip prices from MixedAmount before displaying if not displaying prices.
This commit is contained in:
Stephen Morgan 2021-03-08 16:01:54 +11:00 committed by Simon Michael
parent 16f8ed3d0f
commit d54e276658
3 changed files with 90 additions and 78 deletions

View File

@ -77,6 +77,8 @@ module Hledger.Data.Amount (
styleAmountExceptPrecision,
amountUnstyled,
showAmountB,
showAmountsB,
showAmountsLinesB,
showAmount,
cshowAmount,
showAmountWithZeroCommodity,
@ -132,7 +134,6 @@ module Hledger.Data.Amount (
showMixedAmountElided,
showMixedAmountWithZeroCommodity,
showMixedAmountB,
showMixedAmountLinesB,
wbToText,
wbUnpack,
mixedAmountSetPrecision,
@ -172,7 +173,6 @@ data AmountDisplayOpts = AmountDisplayOpts
{ displayPrice :: Bool -- ^ Whether to display the Price of an Amount.
, displayZeroCommodity :: Bool -- ^ If the Amount rounds to 0, whether to display its commodity string.
, displayColour :: Bool -- ^ Whether to colourise negative Amounts.
, displayNormalised :: Bool -- ^ Whether to normalise MixedAmounts before displaying.
, displayOneLine :: Bool -- ^ Whether to display on one line.
, displayMinWidth :: Maybe Int -- ^ Minimum width to pad to
, displayMaxWidth :: Maybe Int -- ^ Maximum width to clip to
@ -186,7 +186,6 @@ noColour :: AmountDisplayOpts
noColour = AmountDisplayOpts { displayPrice = True
, displayColour = False
, displayZeroCommodity = False
, displayNormalised = True
, displayOneLine = False
, displayMinWidth = Nothing
, displayMaxWidth = Nothing
@ -434,6 +433,78 @@ 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.
-- - 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)
takeFitting m = dropWhileRev (\(a,e) -> m < adTotal (fromMaybe a e))
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.
--
@ -773,79 +844,22 @@ showMixedAmountDebug m | m == missingmixedamt = "(missing)"
| otherwise = printf "Mixed [%s]" as
where as = intercalate "\n " $ map showAmountDebug $ amounts m
-- | General function to generate a WideBuilder for a MixedAmount, according the
-- | General function to generate a WideBuilder for a MixedAmount, according to the
-- supplied AmountDisplayOpts. This is the main function to use for showing
-- 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.
-- - If displayed on multiple lines, any Amounts longer than the
-- maximum width will be elided.
showMixedAmountB :: AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB opts ma
| displayOneLine opts = showMixedAmountOneLineB opts ma'
| otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width
where
ma' = if displayPrice opts then ma else mixedAmountStripPrices ma
lines = showMixedAmountLinesB opts ma'
width = headDef 0 $ map wbWidth lines
sep = WideBuilder (TB.singleton '\n') 0
-- | Helper for showMixedAmountB to show a MixedAmount on multiple lines. This returns
-- the list of WideBuilders: one for each Amount in the MixedAmount (possibly
-- normalised), 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
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
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 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
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
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)
takeFitting m = dropWhileRev (\(a,e) -> m < adTotal (fromMaybe a e))
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]
showMixedAmountB opts = showAmountsB opts . amounts
. (if displayPrice opts then id else mixedAmountStripPrices) . normaliseMixedAmountSquashPricesForDisplay
data AmountDisplay = AmountDisplay
{ adBuilder :: !WideBuilder -- ^ String representation of the Amount

View File

@ -273,10 +273,10 @@ postingAsLines elideamount onelineamounts pstoalignwith p =
-- currently prices are considered part of the amount string when right-aligning amounts
shownAmounts
| elideamount || null (amounts $ pamount p) = [mempty]
| otherwise = showMixedAmountLinesB displayopts $ pamount p
| otherwise = showAmountsLinesB displayopts . amounts $ pamount p
where
displayopts = noColour{displayOneLine=onelineamounts, displayMinWidth = Just amtwidth, displayNormalised=False}
amtwidth = maximum $ 12 : map (wbWidth . showMixedAmountB displayopts{displayMinWidth=Nothing} . pamount) pstoalignwith -- min. 12 for backwards compatibility
displayopts = noColour{displayOneLine=onelineamounts, displayMinWidth = Just amtwidth}
amtwidth = maximum $ 12 : map (wbWidth . showAmountsB displayopts{displayMinWidth=Nothing} . amounts . pamount) pstoalignwith -- min. 12 for backwards compatibility
(samelinecomment, newlinecomments) =
case renderCommentLines (pcomment p) of [] -> ("",[])

View File

@ -335,11 +335,10 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
)
where
sameamount (p1,p2) = mixedAmountUnstyled (pamount p1) == mixedAmountUnstyled (pamount p2)
def = case (esArgs, mhistoricalp, followedhistoricalsofar) of
(d:_,_,_) -> d
(_,Just hp,True) -> showamt $ pamount hp
_ | pnum > 1 && not (mixedAmountLooksZero balancingamt) -> showamt balancingamtfirstcommodity
_ -> ""
def | (d:_) <- esArgs = d
| Just hp <- mhistoricalp, followedhistoricalsofar = showamt . amounts $ 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\"." $
parser parseAmountAndComment $
withCompletion (amountCompleter def) $
@ -361,9 +360,8 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
-- eof
return (a,c)
balancingamt = maNegate . sumPostings $ filter isReal esPostings
balancingamtfirstcommodity = mixed . take 1 $ amounts balancingamt
showamt =
showMixedAmount . mixedAmountSetPrecision
balancingamtfirstcommodity = take 1 $ amounts balancingamt
showamt = wbUnpack . showAmountsB noColour . map (amountSetPrecision
-- 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) ?
@ -371,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