lib: Make consistent naming scheme for showMixedAmount* functions,
add conversion between old API and new API in the documentation.
This commit is contained in:
parent
1f891a4145
commit
7d3cf1747a
@ -30,8 +30,8 @@ instance Show Account where
|
|||||||
aname
|
aname
|
||||||
(if aboring then "y" else "n" :: String)
|
(if aboring then "y" else "n" :: String)
|
||||||
anumpostings
|
anumpostings
|
||||||
(wbUnpack $ showMixed noColour aebalance)
|
(wbUnpack $ showMixedAmountB noColour aebalance)
|
||||||
(wbUnpack $ showMixed noColour aibalance)
|
(wbUnpack $ showMixedAmountB noColour aibalance)
|
||||||
|
|
||||||
instance Eq Account where
|
instance Eq Account where
|
||||||
(==) a b = aname a == aname b -- quick equality test for speed
|
(==) a b = aname a == aname b -- quick equality test for speed
|
||||||
@ -265,6 +265,6 @@ showAccountsBoringFlag = unlines . map (show . aboring) . flattenAccounts
|
|||||||
|
|
||||||
showAccountDebug a = printf "%-25s %4s %4s %s"
|
showAccountDebug a = printf "%-25s %4s %4s %s"
|
||||||
(aname a)
|
(aname a)
|
||||||
(wbUnpack . showMixed noColour $ aebalance a)
|
(wbUnpack . showMixedAmountB noColour $ aebalance a)
|
||||||
(wbUnpack . showMixed noColour $ aibalance a)
|
(wbUnpack . showMixedAmountB noColour $ aibalance a)
|
||||||
(if aboring a then "b" else " " :: String)
|
(if aboring a then "b" else " " :: String)
|
||||||
|
|||||||
@ -125,8 +125,10 @@ module Hledger.Data.Amount (
|
|||||||
showMixedAmountOneLineWithoutPrice,
|
showMixedAmountOneLineWithoutPrice,
|
||||||
showMixedAmountElided,
|
showMixedAmountElided,
|
||||||
showMixedAmountWithZeroCommodity,
|
showMixedAmountWithZeroCommodity,
|
||||||
showMixed,
|
showMixedAmountB,
|
||||||
showMixedLines,
|
showMixedAmountLinesB,
|
||||||
|
wbToText,
|
||||||
|
wbUnpack,
|
||||||
setMixedAmountPrecision,
|
setMixedAmountPrecision,
|
||||||
canonicaliseMixedAmount,
|
canonicaliseMixedAmount,
|
||||||
-- * misc.
|
-- * misc.
|
||||||
@ -403,12 +405,16 @@ amountUnstyled a = a{astyle=amountstyle}
|
|||||||
-- commodity's display settings. String representations equivalent to
|
-- commodity's display settings. String representations equivalent to
|
||||||
-- zero are converted to just \"0\". The special "missing" amount is
|
-- zero are converted to just \"0\". The special "missing" amount is
|
||||||
-- displayed as the empty string.
|
-- displayed as the empty string.
|
||||||
|
--
|
||||||
|
-- > showAmount = wbUnpack . showAmountB noColour
|
||||||
showAmount :: Amount -> String
|
showAmount :: Amount -> String
|
||||||
showAmount = wbUnpack . showAmountB noColour
|
showAmount = wbUnpack . showAmountB noColour
|
||||||
|
|
||||||
-- | Get the string representation of an amount, based on its
|
-- | General function to generate a WideBuilder for an Amount, according the
|
||||||
-- commodity's display settings and the display options. The
|
-- supplied AmountDisplayOpts. The special "missing" amount is displayed as
|
||||||
-- special "missing" amount is displayed as the empty string.
|
-- the empty string. This is the main function to use for showing
|
||||||
|
-- Amounts, constructing a builder; it can then be converted to a Text with
|
||||||
|
-- wbToText, or to a String with wbUnpack.
|
||||||
showAmountB :: AmountDisplayOpts -> Amount -> WideBuilder
|
showAmountB :: AmountDisplayOpts -> Amount -> WideBuilder
|
||||||
showAmountB _ Amount{acommodity="AUTO"} = mempty
|
showAmountB _ Amount{acommodity="AUTO"} = mempty
|
||||||
showAmountB opts a@Amount{astyle=style} =
|
showAmountB opts a@Amount{astyle=style} =
|
||||||
@ -426,14 +432,20 @@ showAmountB opts a@Amount{astyle=style} =
|
|||||||
|
|
||||||
-- | 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.
|
||||||
|
--
|
||||||
|
-- > cshowAmount = wbUnpack . showAmountB def{displayColour=True}
|
||||||
cshowAmount :: Amount -> String
|
cshowAmount :: Amount -> String
|
||||||
cshowAmount = wbUnpack . showAmountB def
|
cshowAmount = wbUnpack . showAmountB def{displayColour=True}
|
||||||
|
|
||||||
-- | Get the string representation of an amount, without any \@ price.
|
-- | Get the string representation of an amount, without any \@ price.
|
||||||
|
--
|
||||||
|
-- > showAmountWithoutPrice = wbUnpack . showAmountB noPrice
|
||||||
showAmountWithoutPrice :: Amount -> String
|
showAmountWithoutPrice :: Amount -> String
|
||||||
showAmountWithoutPrice = wbUnpack . showAmountB noPrice
|
showAmountWithoutPrice = wbUnpack . showAmountB noPrice
|
||||||
|
|
||||||
-- | Like showAmount, but show a zero amount's commodity if it has one.
|
-- | Like showAmount, but show a zero amount's commodity if it has one.
|
||||||
|
--
|
||||||
|
-- > showAmountWithZeroCommodity = wbUnpack . showAmountB noColour{displayZeryCommodity=True}
|
||||||
showAmountWithZeroCommodity :: Amount -> String
|
showAmountWithZeroCommodity :: Amount -> String
|
||||||
showAmountWithZeroCommodity = wbUnpack . showAmountB noColour{displayZeroCommodity=True}
|
showAmountWithZeroCommodity = wbUnpack . showAmountB noColour{displayZeroCommodity=True}
|
||||||
|
|
||||||
@ -668,34 +680,46 @@ mixedAmountUnstyled = mapMixedAmount amountUnstyled
|
|||||||
-- | Get the string representation of a mixed amount, after
|
-- | Get the string representation of a mixed amount, after
|
||||||
-- normalising it to one amount per commodity. Assumes amounts have
|
-- normalising it to one amount per commodity. Assumes amounts have
|
||||||
-- no or similar prices, otherwise this can show misleading prices.
|
-- no or similar prices, otherwise this can show misleading prices.
|
||||||
|
--
|
||||||
|
-- > showMixedAmount = wbUnpack . showMixedAmountB noColour
|
||||||
showMixedAmount :: MixedAmount -> String
|
showMixedAmount :: MixedAmount -> String
|
||||||
showMixedAmount = wbUnpack . showMixed noColour
|
showMixedAmount = wbUnpack . showMixedAmountB noColour
|
||||||
|
|
||||||
-- | Get the one-line string representation of a mixed amount.
|
-- | Get the one-line string representation of a mixed amount.
|
||||||
|
--
|
||||||
|
-- > showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine
|
||||||
showMixedAmountOneLine :: MixedAmount -> String
|
showMixedAmountOneLine :: MixedAmount -> String
|
||||||
showMixedAmountOneLine = wbUnpack . showMixed oneLine
|
showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine
|
||||||
|
|
||||||
-- | 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.
|
||||||
|
--
|
||||||
|
-- > showMixedAmountWithZeroCommodity = wbUnpack . showMixedAmountB noColour{displayZeroCommodity=True}
|
||||||
showMixedAmountWithZeroCommodity :: MixedAmount -> String
|
showMixedAmountWithZeroCommodity :: MixedAmount -> String
|
||||||
showMixedAmountWithZeroCommodity = wbUnpack . showMixed noColour{displayZeroCommodity=True}
|
showMixedAmountWithZeroCommodity = wbUnpack . showMixedAmountB noColour{displayZeroCommodity=True}
|
||||||
|
|
||||||
-- | Get the string representation of a mixed amount, without showing any transaction prices.
|
-- | Get the string representation of a mixed amount, without showing any transaction prices.
|
||||||
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
||||||
|
--
|
||||||
|
-- > showMixedAmountWithoutPrice c = wbUnpack . showMixedAmountB noPrice{displayColour=c}
|
||||||
showMixedAmountWithoutPrice :: Bool -> MixedAmount -> String
|
showMixedAmountWithoutPrice :: Bool -> MixedAmount -> String
|
||||||
showMixedAmountWithoutPrice c = wbUnpack . showMixed noPrice{displayColour=c}
|
showMixedAmountWithoutPrice c = wbUnpack . showMixedAmountB noPrice{displayColour=c}
|
||||||
|
|
||||||
-- | Get the one-line string representation of a mixed amount, but without
|
-- | Get the one-line string representation of a mixed amount, but without
|
||||||
-- any \@ prices.
|
-- any \@ prices.
|
||||||
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
||||||
|
--
|
||||||
|
-- > showMixedAmountOneLineWithoutPrice c = wbUnpack . showMixedAmountB oneLine{displayColour=c}
|
||||||
showMixedAmountOneLineWithoutPrice :: Bool -> MixedAmount -> String
|
showMixedAmountOneLineWithoutPrice :: Bool -> MixedAmount -> String
|
||||||
showMixedAmountOneLineWithoutPrice c = wbUnpack . showMixed oneLine{displayColour=c}
|
showMixedAmountOneLineWithoutPrice c = wbUnpack . showMixedAmountB oneLine{displayColour=c}
|
||||||
|
|
||||||
-- | Like showMixedAmountOneLineWithoutPrice, but show at most the given width,
|
-- | Like showMixedAmountOneLineWithoutPrice, but show at most the given width,
|
||||||
-- with an elision indicator if there are more.
|
-- with an elision indicator if there are more.
|
||||||
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
||||||
|
--
|
||||||
|
-- > showMixedAmountElided w c = wbUnpack . showMixedAmountB oneLine{displayColour=c, displayMaxWidth=Just w}
|
||||||
showMixedAmountElided :: Int -> Bool -> MixedAmount -> String
|
showMixedAmountElided :: Int -> Bool -> MixedAmount -> String
|
||||||
showMixedAmountElided w c = wbUnpack . showMixed oneLine{displayColour=c, displayMaxWidth=Just w}
|
showMixedAmountElided w c = wbUnpack . showMixedAmountB oneLine{displayColour=c, displayMaxWidth=Just w}
|
||||||
|
|
||||||
-- | Get an unambiguous string representation of a mixed amount for debugging.
|
-- | Get an unambiguous string representation of a mixed amount for debugging.
|
||||||
showMixedAmountDebug :: MixedAmount -> String
|
showMixedAmountDebug :: MixedAmount -> String
|
||||||
@ -703,29 +727,32 @@ showMixedAmountDebug m | m == missingmixedamt = "(missing)"
|
|||||||
| otherwise = printf "Mixed [%s]" as
|
| otherwise = printf "Mixed [%s]" as
|
||||||
where as = intercalate "\n " $ map showAmountDebug $ amounts m
|
where as = intercalate "\n " $ map showAmountDebug $ amounts m
|
||||||
|
|
||||||
-- | General function to generate a WideBuilder for a MixedAmount,
|
-- | General function to generate a WideBuilder for a MixedAmount, according the
|
||||||
-- according the supplied AmountDisplayOpts. If a maximum width is
|
-- supplied AmountDisplayOpts. This is the main function to use for showing
|
||||||
-- given then:
|
-- MixedAmounts, constructing a builder; it can then be converted to a Text with
|
||||||
|
-- wbToText, or to a String with wbUnpack.
|
||||||
|
--
|
||||||
|
-- If a maximum width is given then:
|
||||||
-- - If displayed on one line, it will display as many Amounts as can
|
-- - 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.
|
||||||
-- - If displayed on multiple lines, any Amounts longer than the
|
-- - If displayed on multiple lines, any Amounts longer than the
|
||||||
-- maximum width will be elided.
|
-- maximum width will be elided.
|
||||||
showMixed :: AmountDisplayOpts -> MixedAmount -> WideBuilder
|
showMixedAmountB :: AmountDisplayOpts -> MixedAmount -> WideBuilder
|
||||||
showMixed opts ma
|
showMixedAmountB opts ma
|
||||||
| displayOneLine opts = showMixedOneLine opts ma
|
| displayOneLine opts = showMixedAmountOneLineB opts ma
|
||||||
| otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width
|
| otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width
|
||||||
where
|
where
|
||||||
lines = showMixedLines opts ma
|
lines = showMixedAmountLinesB opts ma
|
||||||
width = headDef 0 $ map wbWidth lines
|
width = headDef 0 $ map wbWidth lines
|
||||||
sep = WideBuilder (TB.singleton '\n') 0
|
sep = WideBuilder (TB.singleton '\n') 0
|
||||||
|
|
||||||
-- | Helper for showMixed to show a MixedAmount on multiple lines. This returns
|
-- | Helper for showMixedAmountB to show a MixedAmount on multiple lines. This returns
|
||||||
-- the list of WideBuilders: one for each Amount in the MixedAmount (possibly
|
-- the list of WideBuilders: one for each Amount in the MixedAmount (possibly
|
||||||
-- normalised), and padded/elided to the appropriate width. This does not
|
-- normalised), and padded/elided to the appropriate width. This does not
|
||||||
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
|
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
|
||||||
-- were False.
|
-- were False.
|
||||||
showMixedLines :: AmountDisplayOpts -> MixedAmount -> [WideBuilder]
|
showMixedAmountLinesB :: AmountDisplayOpts -> MixedAmount -> [WideBuilder]
|
||||||
showMixedLines opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
|
showMixedAmountLinesB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
|
||||||
map (adBuilder . pad) elided
|
map (adBuilder . pad) elided
|
||||||
where
|
where
|
||||||
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
|
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
|
||||||
@ -743,11 +770,11 @@ showMixedLines opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin}
|
|||||||
elisionStr = elisionDisplay (Just m) (wbWidth sep) (length long) $ lastDef nullAmountDisplay short
|
elisionStr = elisionDisplay (Just m) (wbWidth sep) (length long) $ lastDef nullAmountDisplay short
|
||||||
(short, long) = partition ((m>=) . wbWidth . adBuilder) xs
|
(short, long) = partition ((m>=) . wbWidth . adBuilder) xs
|
||||||
|
|
||||||
-- | Helper for showMixed to deal with single line displays. This does not
|
-- | Helper for showMixedAmountB to deal with single line displays. This does not
|
||||||
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
|
-- honour displayOneLine: all amounts will be displayed as if displayOneLine
|
||||||
-- were True.
|
-- were True.
|
||||||
showMixedOneLine :: AmountDisplayOpts -> MixedAmount -> WideBuilder
|
showMixedAmountOneLineB :: AmountDisplayOpts -> MixedAmount -> WideBuilder
|
||||||
showMixedOneLine opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
|
showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma =
|
||||||
WideBuilder (wbBuilder . pad . mconcat . intersperse sep $ map adBuilder elided) . max width $ fromMaybe 0 mmin
|
WideBuilder (wbBuilder . pad . mconcat . intersperse sep $ map adBuilder elided) . max width $ fromMaybe 0 mmin
|
||||||
where
|
where
|
||||||
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
|
Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma
|
||||||
|
|||||||
@ -170,7 +170,7 @@ showPosting p@Posting{paccount=a,pamount=amt,ptype=t} =
|
|||||||
BalancedVirtualPosting -> (wrap "[" "]", acctnamewidth-2)
|
BalancedVirtualPosting -> (wrap "[" "]", acctnamewidth-2)
|
||||||
VirtualPosting -> (wrap "(" ")", acctnamewidth-2)
|
VirtualPosting -> (wrap "(" ")", acctnamewidth-2)
|
||||||
_ -> (id,acctnamewidth)
|
_ -> (id,acctnamewidth)
|
||||||
showamount = wbUnpack . showMixed noColour{displayMinWidth=Just 12}
|
showamount = wbUnpack . showMixedAmountB noColour{displayMinWidth=Just 12}
|
||||||
|
|
||||||
|
|
||||||
showComment :: Text -> Text
|
showComment :: Text -> Text
|
||||||
|
|||||||
@ -268,10 +268,10 @@ postingAsLines elideamount onelineamounts pstoalignwith p =
|
|||||||
-- currently prices are considered part of the amount string when right-aligning amounts
|
-- currently prices are considered part of the amount string when right-aligning amounts
|
||||||
shownAmounts
|
shownAmounts
|
||||||
| elideamount || null (amounts $ pamount p) = [mempty]
|
| elideamount || null (amounts $ pamount p) = [mempty]
|
||||||
| otherwise = showMixedLines displayopts $ pamount p
|
| otherwise = showMixedAmountLinesB displayopts $ pamount p
|
||||||
where
|
where
|
||||||
displayopts = noColour{displayOneLine=onelineamounts, displayMinWidth = Just amtwidth, displayNormalised=False}
|
displayopts = noColour{displayOneLine=onelineamounts, displayMinWidth = Just amtwidth, displayNormalised=False}
|
||||||
amtwidth = maximum $ 12 : map (wbWidth . showMixed displayopts{displayMinWidth=Nothing} . pamount) pstoalignwith -- min. 12 for backwards compatibility
|
amtwidth = maximum $ 12 : map (wbWidth . showMixedAmountB displayopts{displayMinWidth=Nothing} . pamount) pstoalignwith -- min. 12 for backwards compatibility
|
||||||
|
|
||||||
(samelinecomment, newlinecomments) =
|
(samelinecomment, newlinecomments) =
|
||||||
case renderCommentLines (pcomment p) of [] -> ("",[])
|
case renderCommentLines (pcomment p) of [] -> ("",[])
|
||||||
|
|||||||
@ -1024,7 +1024,7 @@ getAmount rules record currency p1IsVirtual n =
|
|||||||
]
|
]
|
||||||
++ [" assignment: " <> f <> " " <>
|
++ [" assignment: " <> f <> " " <>
|
||||||
fromMaybe "" (hledgerField rules record f) <>
|
fromMaybe "" (hledgerField rules record f) <>
|
||||||
"\t=> value: " <> wbToText (showMixed noColour a) -- XXX not sure this is showing all the right info
|
"\t=> value: " <> wbToText (showMixedAmountB noColour a) -- XXX not sure this is showing all the right info
|
||||||
| (f,a) <- fs]
|
| (f,a) <- fs]
|
||||||
|
|
||||||
-- | Figure out the expected balance (assertion or assignment) specified for posting N,
|
-- | Figure out the expected balance (assertion or assignment) specified for posting N,
|
||||||
|
|||||||
@ -244,7 +244,7 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $
|
|||||||
where
|
where
|
||||||
actual' = fromMaybe 0 actual
|
actual' = fromMaybe 0 actual
|
||||||
budgetAndPerc b = (showamt b, showper <$> percentage actual' b)
|
budgetAndPerc b = (showamt b, showper <$> percentage actual' b)
|
||||||
showamt = (\(WideBuilder b w) -> (TL.toStrict $ TB.toLazyText b, w)) . showMixed oneLine{displayColour=color_, displayMaxWidth=Just 32}
|
showamt = (\(WideBuilder b w) -> (TL.toStrict $ TB.toLazyText b, w)) . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=Just 32}
|
||||||
showper p = let str = T.pack (show $ roundTo 0 p) in (str, T.length str)
|
showper p = let str = T.pack (show $ roundTo 0 p) in (str, T.length str)
|
||||||
cellWidth ((_,wa), Nothing) = (wa, 0, 0)
|
cellWidth ((_,wa), Nothing) = (wa, 0, 0)
|
||||||
cellWidth ((_,wa), Just ((_,wb), Nothing)) = (wa, wb, 0)
|
cellWidth ((_,wa), Just ((_,wb), Nothing)) = (wa, wb, 0)
|
||||||
@ -380,7 +380,7 @@ budgetReportAsCsv
|
|||||||
|
|
||||||
where
|
where
|
||||||
flattentuples abs = concat [[a,b] | (a,b) <- abs]
|
flattentuples abs = concat [[a,b] | (a,b) <- abs]
|
||||||
showmamt = maybe "" (wbToText . showMixed oneLine)
|
showmamt = maybe "" (wbToText . showMixedAmountB oneLine)
|
||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
|
|||||||
@ -98,7 +98,7 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
|
|||||||
,rsItemTransaction = t
|
,rsItemTransaction = t
|
||||||
}
|
}
|
||||||
where showamt = (\wb -> (wbUnpack wb, wbWidth wb))
|
where showamt = (\wb -> (wbUnpack wb, wbWidth wb))
|
||||||
. showMixed oneLine{displayMaxWidth=Just 32}
|
. showMixedAmountB oneLine{displayMaxWidth=Just 32}
|
||||||
-- blank items are added to allow more control of scroll position; we won't allow movement over these.
|
-- blank items are added to allow more control of scroll position; we won't allow movement over these.
|
||||||
-- XXX Ugly. Changing to 0 helps when debugging.
|
-- XXX Ugly. Changing to 0 helps when debugging.
|
||||||
blankitems = replicate 100 -- "100 ought to be enough for anyone"
|
blankitems = replicate 100 -- "100 ought to be enough for anyone"
|
||||||
|
|||||||
@ -131,8 +131,8 @@ accountTransactionsReportItemAsCsvRecord
|
|||||||
where
|
where
|
||||||
idx = T.pack $ show tindex
|
idx = T.pack $ show tindex
|
||||||
date = showDate $ transactionRegisterDate reportq thisacctq t
|
date = showDate $ transactionRegisterDate reportq thisacctq t
|
||||||
amt = wbToText $ showMixed oneLine change
|
amt = wbToText $ showMixedAmountB oneLine change
|
||||||
bal = wbToText $ showMixed oneLine balance
|
bal = wbToText $ showMixedAmountB oneLine balance
|
||||||
|
|
||||||
-- | Render a register report as plain text suitable for console output.
|
-- | Render a register report as plain text suitable for console output.
|
||||||
accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text
|
accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text
|
||||||
@ -143,7 +143,7 @@ accountTransactionsReportAsText copts reportq thisacctq items
|
|||||||
where
|
where
|
||||||
amtwidth = maximumStrict $ 12 : map (wbWidth . showamt . itemamt) items
|
amtwidth = maximumStrict $ 12 : map (wbWidth . showamt . itemamt) items
|
||||||
balwidth = maximumStrict $ 12 : map (wbWidth . showamt . itembal) items
|
balwidth = maximumStrict $ 12 : map (wbWidth . showamt . itembal) items
|
||||||
showamt = showMixed oneLine{displayMinWidth=Just 12, displayMaxWidth=mmax} -- color_
|
showamt = showMixedAmountB oneLine{displayMinWidth=Just 12, displayMaxWidth=mmax} -- color_
|
||||||
where mmax = if no_elide_ . rsOpts . reportspec_ $ copts then Nothing else Just 32
|
where mmax = if no_elide_ . rsOpts . reportspec_ $ copts then Nothing else Just 32
|
||||||
itemamt (_,_,_,_,a,_) = a
|
itemamt (_,_,_,_,a,_) = a
|
||||||
itembal (_,_,_,_,_,a) = a
|
itembal (_,_,_,_,_,a) = a
|
||||||
@ -215,7 +215,7 @@ accountTransactionsReportItemAsText
|
|||||||
otheracctsstr
|
otheracctsstr
|
||||||
amt = TL.toStrict . TB.toLazyText . wbBuilder $ showamt amtwidth change
|
amt = TL.toStrict . TB.toLazyText . wbBuilder $ showamt amtwidth change
|
||||||
bal = TL.toStrict . TB.toLazyText . wbBuilder $ showamt balwidth balance
|
bal = TL.toStrict . TB.toLazyText . wbBuilder $ showamt balwidth balance
|
||||||
showamt w = showMixed noPrice{displayColour=color_, displayMinWidth=Just w, displayMaxWidth=Just w}
|
showamt w = showMixedAmountB noPrice{displayColour=color_, displayMinWidth=Just w, displayMaxWidth=Just w}
|
||||||
-- alternate behaviour, show null amounts as 0 instead of blank
|
-- alternate behaviour, show null amounts as 0 instead of blank
|
||||||
-- amt = if null amt' then "0" else amt'
|
-- amt = if null amt' then "0" else amt'
|
||||||
-- bal = if null bal' then "0" else bal'
|
-- bal = if null bal' then "0" else bal'
|
||||||
|
|||||||
@ -357,11 +357,11 @@ balance opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
|||||||
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
||||||
balanceReportAsCsv opts (items, total) =
|
balanceReportAsCsv opts (items, total) =
|
||||||
["account","balance"] :
|
["account","balance"] :
|
||||||
[[a, wbToText $ showMixed oneLine b] | (a, _, _, b) <- items]
|
[[a, wbToText $ showMixedAmountB oneLine b] | (a, _, _, b) <- items]
|
||||||
++
|
++
|
||||||
if no_total_ opts
|
if no_total_ opts
|
||||||
then []
|
then []
|
||||||
else [["total", wbToText $ showMixed oneLine total]]
|
else [["total", wbToText $ showMixedAmountB oneLine total]]
|
||||||
|
|
||||||
-- | Render a single-column balance report as plain text.
|
-- | Render a single-column balance report as plain text.
|
||||||
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
||||||
@ -438,7 +438,7 @@ renderComponent topaligned opts (acctname, depth, total) (FormatField ljust mmin
|
|||||||
where
|
where
|
||||||
align = if topaligned then (if ljust then TopLeft else TopRight)
|
align = if topaligned then (if ljust then TopLeft else TopRight)
|
||||||
else (if ljust then BottomLeft else BottomRight)
|
else (if ljust then BottomLeft else BottomRight)
|
||||||
showamt = showMixed noPrice{displayColour=color_ opts, displayMinWidth=mmin, displayMaxWidth=mmax}
|
showamt = showMixedAmountB noPrice{displayColour=color_ opts, displayMinWidth=mmin, displayMaxWidth=mmax}
|
||||||
|
|
||||||
-- rendering multi-column balance reports
|
-- rendering multi-column balance reports
|
||||||
|
|
||||||
@ -454,7 +454,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
|
|||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
) :
|
) :
|
||||||
[displayFull a :
|
[displayFull a :
|
||||||
map (wbToText . showMixed oneLine)
|
map (wbToText . showMixedAmountB oneLine)
|
||||||
(amts
|
(amts
|
||||||
++ [rowtot | row_total_]
|
++ [rowtot | row_total_]
|
||||||
++ [rowavg | average_])
|
++ [rowavg | average_])
|
||||||
@ -463,7 +463,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
|
|||||||
if no_total_ opts
|
if no_total_ opts
|
||||||
then []
|
then []
|
||||||
else ["Total:" :
|
else ["Total:" :
|
||||||
map (wbToText . showMixed oneLine) (
|
map (wbToText . showMixedAmountB oneLine) (
|
||||||
coltotals
|
coltotals
|
||||||
++ [tot | row_total_]
|
++ [tot | row_total_]
|
||||||
++ [avg | average_]
|
++ [avg | average_]
|
||||||
@ -627,7 +627,7 @@ balanceReportTableAsText ReportOpts{..} =
|
|||||||
Tab.renderTableB def{tableBorders=False, prettyTable=pretty_tables_}
|
Tab.renderTableB def{tableBorders=False, prettyTable=pretty_tables_}
|
||||||
(Tab.alignCell TopLeft) (Tab.alignCell TopRight) showamt
|
(Tab.alignCell TopLeft) (Tab.alignCell TopRight) showamt
|
||||||
where
|
where
|
||||||
showamt = Cell TopRight . pure . showMixed oneLine{displayColour=color_, displayMaxWidth=mmax}
|
showamt = Cell TopRight . pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=mmax}
|
||||||
mmax = if no_elide_ then Nothing else Just 32
|
mmax = if no_elide_ then Nothing else Just 32
|
||||||
|
|
||||||
|
|
||||||
|
|||||||
@ -90,8 +90,8 @@ postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,code,desc,acct,amt,bal
|
|||||||
BalancedVirtualPosting -> wrap "[" "]"
|
BalancedVirtualPosting -> wrap "[" "]"
|
||||||
VirtualPosting -> wrap "(" ")"
|
VirtualPosting -> wrap "(" ")"
|
||||||
_ -> id
|
_ -> id
|
||||||
amt = wbToText . showMixed oneLine $ pamount p
|
amt = wbToText . showMixedAmountB oneLine $ pamount p
|
||||||
bal = wbToText $ showMixed oneLine b
|
bal = wbToText $ showMixedAmountB oneLine b
|
||||||
|
|
||||||
-- | Render a register report as plain text suitable for console output.
|
-- | Render a register report as plain text suitable for console output.
|
||||||
postingsReportAsText :: CliOpts -> PostingsReport -> TL.Text
|
postingsReportAsText :: CliOpts -> PostingsReport -> TL.Text
|
||||||
@ -105,7 +105,7 @@ postingsReportAsText opts items =
|
|||||||
itembal (_,_,_,_,a) = a
|
itembal (_,_,_,_,a) = a
|
||||||
unlinesB [] = mempty
|
unlinesB [] = mempty
|
||||||
unlinesB xs = mconcat (intersperse (TB.fromText "\n") xs) <> TB.fromText "\n"
|
unlinesB xs = mconcat (intersperse (TB.fromText "\n") xs) <> TB.fromText "\n"
|
||||||
showAmt = showMixed noColour{displayMinWidth=Just 12}
|
showAmt = showMixedAmountB noColour{displayMinWidth=Just 12}
|
||||||
|
|
||||||
-- | Render one register report line item as plain text. Layout is like so:
|
-- | Render one register report line item as plain text. Layout is like so:
|
||||||
-- @
|
-- @
|
||||||
@ -185,7 +185,7 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
|
|||||||
wrap a b x = a <> x <> b
|
wrap a b x = a <> x <> b
|
||||||
amt = TL.toStrict . TB.toLazyText . wbBuilder . showamt amtwidth $ pamount p
|
amt = TL.toStrict . TB.toLazyText . wbBuilder . showamt amtwidth $ pamount p
|
||||||
bal = TL.toStrict . TB.toLazyText . wbBuilder $ showamt balwidth b
|
bal = TL.toStrict . TB.toLazyText . wbBuilder $ showamt balwidth b
|
||||||
showamt w = showMixed noPrice{displayColour=color_ . rsOpts $ reportspec_ opts, displayMinWidth=Just w, displayMaxWidth=Just w}
|
showamt w = showMixedAmountB noPrice{displayColour=color_ . rsOpts $ reportspec_ opts, displayMinWidth=Just w, displayMaxWidth=Just w}
|
||||||
-- alternate behaviour, show null amounts as 0 instead of blank
|
-- alternate behaviour, show null amounts as 0 instead of blank
|
||||||
-- amt = if null amt' then "0" else amt'
|
-- amt = if null amt' then "0" else amt'
|
||||||
-- bal = if null bal' then "0" else bal'
|
-- bal = if null bal' then "0" else bal'
|
||||||
|
|||||||
@ -263,7 +263,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor
|
|||||||
| no_total_ ropts || length subreports == 1 = id
|
| no_total_ ropts || length subreports == 1 = id
|
||||||
| otherwise = (++
|
| otherwise = (++
|
||||||
["Net:" :
|
["Net:" :
|
||||||
map (wbToText . showMixed oneLine) (
|
map (wbToText . showMixedAmountB oneLine) (
|
||||||
coltotals
|
coltotals
|
||||||
++ (if row_total_ ropts then [grandtotal] else [])
|
++ (if row_total_ ropts then [grandtotal] else [])
|
||||||
++ (if average_ ropts then [grandavg] else [])
|
++ (if average_ ropts then [grandavg] else [])
|
||||||
@ -309,9 +309,9 @@ compoundBalanceReportAsHtml ropts cbr =
|
|||||||
let defstyle = style_ "text-align:right"
|
let defstyle = style_ "text-align:right"
|
||||||
orEmpty b x = if b then x else mempty
|
orEmpty b x = if b then x else mempty
|
||||||
in [tr_ $ th_ [class_ "", style_ "text-align:left"] "Net:"
|
in [tr_ $ th_ [class_ "", style_ "text-align:left"] "Net:"
|
||||||
<> foldMap (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack . showMixed oneLine) coltotals
|
<> foldMap (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack . showMixedAmountB oneLine) coltotals
|
||||||
<> orEmpty (row_total_ ropts) (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack $ showMixed oneLine grandtotal)
|
<> orEmpty (row_total_ ropts) (th_ [class_ "amount coltotal", defstyle] . toHtml . wbUnpack $ showMixedAmountB oneLine grandtotal)
|
||||||
<> orEmpty (average_ ropts) (th_ [class_ "amount colaverage", defstyle] . toHtml . wbUnpack $ showMixed oneLine grandavg)
|
<> orEmpty (average_ ropts) (th_ [class_ "amount colaverage", defstyle] . toHtml . wbUnpack $ showMixedAmountB oneLine grandavg)
|
||||||
]
|
]
|
||||||
in do
|
in do
|
||||||
style_ (T.unlines [""
|
style_ (T.unlines [""
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user