add a color argument to most amount show helpers, drop cshow variants
This is an API change, but it seems better than having additional colour-supporting variants and trying to avoid duplicated code. I stopped short of changing showAmount, so cshowAmount still exists.
This commit is contained in:
		
							parent
							
								
									2739a70a38
								
							
						
					
					
						commit
						44c3eb1904
					
				@ -122,9 +122,6 @@ module Hledger.Data.Amount (
 | 
				
			|||||||
  showMixedAmountWithoutPrice,
 | 
					  showMixedAmountWithoutPrice,
 | 
				
			||||||
  showMixedAmountOneLineWithoutPrice,
 | 
					  showMixedAmountOneLineWithoutPrice,
 | 
				
			||||||
  showMixedAmountElided,
 | 
					  showMixedAmountElided,
 | 
				
			||||||
  cshowMixedAmountWithoutPrice,
 | 
					 | 
				
			||||||
  cshowMixedAmountOneLineWithoutPrice,
 | 
					 | 
				
			||||||
  cshowMixedAmountElided,
 | 
					 | 
				
			||||||
  showMixedAmountWithZeroCommodity,
 | 
					  showMixedAmountWithZeroCommodity,
 | 
				
			||||||
  showMixedAmountWithPrecision,
 | 
					  showMixedAmountWithPrecision,
 | 
				
			||||||
  setMixedAmountPrecision,
 | 
					  setMixedAmountPrecision,
 | 
				
			||||||
@ -150,7 +147,6 @@ import Hledger.Data.Types
 | 
				
			|||||||
import Hledger.Data.Commodity
 | 
					import Hledger.Data.Commodity
 | 
				
			||||||
import Hledger.Utils
 | 
					import Hledger.Utils
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					 | 
				
			||||||
deriving instance Show MarketPrice
 | 
					deriving instance Show MarketPrice
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -272,7 +268,7 @@ digits = "123456789" :: String
 | 
				
			|||||||
-- | Does mixed amount appear to be zero when rendered with its
 | 
					-- | Does mixed amount appear to be zero when rendered with its
 | 
				
			||||||
-- display precision ?
 | 
					-- display precision ?
 | 
				
			||||||
amountLooksZero :: Amount -> Bool
 | 
					amountLooksZero :: Amount -> Bool
 | 
				
			||||||
amountLooksZero = not . any (`elem` digits) . showAmountWithoutPriceOrCommodity
 | 
					amountLooksZero = not . any (`elem` digits) . (showAmountWithoutPriceOrCommodity False)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Is this amount exactly zero, ignoring its display precision ?
 | 
					-- | Is this amount exactly zero, ignoring its display precision ?
 | 
				
			||||||
amountIsZero :: Amount -> Bool
 | 
					amountIsZero :: Amount -> Bool
 | 
				
			||||||
@ -325,8 +321,11 @@ showAmountDebug Amount{acommodity="AUTO"} = "(missing)"
 | 
				
			|||||||
showAmountDebug Amount{..} = printf "Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s}" (show acommodity) (show aquantity) (showAmountPriceDebug aprice) (show astyle)
 | 
					showAmountDebug Amount{..} = printf "Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s}" (show acommodity) (show aquantity) (showAmountPriceDebug aprice) (show astyle)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Get the string representation of an amount, without any \@ price.
 | 
					-- | Get the string representation of an amount, without any \@ price.
 | 
				
			||||||
showAmountWithoutPrice :: Amount -> String
 | 
					-- With a True argument, adds ANSI codes to show negative amounts in red.
 | 
				
			||||||
showAmountWithoutPrice a = showAmount a{aprice=Nothing}
 | 
					showAmountWithoutPrice :: Bool -> Amount -> String
 | 
				
			||||||
 | 
					showAmountWithoutPrice c a = showamt a{aprice=Nothing}
 | 
				
			||||||
 | 
					  where
 | 
				
			||||||
 | 
					    showamt = if c then cshowAmount else showAmount
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Set an amount's internal precision, ie rounds the Decimal representing
 | 
					-- | Set an amount's internal precision, ie rounds the Decimal representing
 | 
				
			||||||
-- the amount's quantity to some number of decimal places.
 | 
					-- the amount's quantity to some number of decimal places.
 | 
				
			||||||
@ -353,13 +352,12 @@ setAmountDecimalPoint mc a@Amount{ astyle=s } = a{ astyle=s{asdecimalpoint=mc} }
 | 
				
			|||||||
withDecimalPoint :: Amount -> Maybe Char -> Amount
 | 
					withDecimalPoint :: Amount -> Maybe Char -> Amount
 | 
				
			||||||
withDecimalPoint = flip setAmountDecimalPoint
 | 
					withDecimalPoint = flip setAmountDecimalPoint
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Colour version.
 | 
					 | 
				
			||||||
cshowAmountWithoutPrice :: Amount -> String
 | 
					 | 
				
			||||||
cshowAmountWithoutPrice a = cshowAmount a{aprice=Nothing}
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Get the string representation of an amount, without any price or commodity symbol.
 | 
					-- | Get the string representation of an amount, without any price or commodity symbol.
 | 
				
			||||||
showAmountWithoutPriceOrCommodity :: Amount -> String
 | 
					-- With a True argument, adds ANSI codes to show negative amounts in red.
 | 
				
			||||||
showAmountWithoutPriceOrCommodity a = showAmount a{acommodity="", aprice=Nothing}
 | 
					showAmountWithoutPriceOrCommodity :: Bool -> Amount -> String
 | 
				
			||||||
 | 
					showAmountWithoutPriceOrCommodity c a = showamt a{acommodity="", aprice=Nothing}
 | 
				
			||||||
 | 
					  where
 | 
				
			||||||
 | 
					    showamt = if c then cshowAmount else showAmount
 | 
				
			||||||
 | 
					
 | 
				
			||||||
showAmountPrice :: Maybe AmountPrice -> String
 | 
					showAmountPrice :: Maybe AmountPrice -> String
 | 
				
			||||||
showAmountPrice Nothing                = ""
 | 
					showAmountPrice Nothing                = ""
 | 
				
			||||||
@ -700,23 +698,14 @@ showMixedAmountDebug m | m == missingmixedamt = "(missing)"
 | 
				
			|||||||
-- TODO these and related fns are comically complicated:
 | 
					-- TODO these and related fns are comically complicated:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | 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.
 | 
				
			||||||
showMixedAmountWithoutPrice :: MixedAmount -> String
 | 
					-- With a True argument, adds ANSI codes to show negative amounts in red.
 | 
				
			||||||
showMixedAmountWithoutPrice m = intercalate "\n" $ map showamt as
 | 
					showMixedAmountWithoutPrice :: Bool -> MixedAmount -> String
 | 
				
			||||||
  where
 | 
					showMixedAmountWithoutPrice c m = intercalate "\n" $ map showamt as
 | 
				
			||||||
    Mixed as = normaliseMixedAmountSquashPricesForDisplay $ mixedAmountStripPrices m
 | 
					 | 
				
			||||||
    showamt = printf (printf "%%%ds" width) . showAmountWithoutPrice
 | 
					 | 
				
			||||||
      where
 | 
					 | 
				
			||||||
        width = maximumDef 0 $ map (length . showAmount) as
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Colour version of showMixedAmountWithoutPrice. Any individual Amount
 | 
					 | 
				
			||||||
-- which is negative is wrapped in ANSI codes to make it display in red.
 | 
					 | 
				
			||||||
cshowMixedAmountWithoutPrice :: MixedAmount -> String
 | 
					 | 
				
			||||||
cshowMixedAmountWithoutPrice m = intercalate "\n" $ map showamt as
 | 
					 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    Mixed as = normaliseMixedAmountSquashPricesForDisplay $ mixedAmountStripPrices m
 | 
					    Mixed as = normaliseMixedAmountSquashPricesForDisplay $ mixedAmountStripPrices m
 | 
				
			||||||
    showamt a =
 | 
					    showamt a =
 | 
				
			||||||
      (if isNegativeAmount a then color Dull Red else id) $
 | 
					      (if c && isNegativeAmount a then color Dull Red else id) $
 | 
				
			||||||
      printf (printf "%%%ds" width) $ showAmountWithoutPrice a
 | 
					      printf (printf "%%%ds" width) $ showAmountWithoutPrice c a
 | 
				
			||||||
      where
 | 
					      where
 | 
				
			||||||
        width = maximumDef 0 $ map (length . showAmount) as
 | 
					        width = maximumDef 0 $ map (length . showAmount) as
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -725,41 +714,21 @@ mixedAmountStripPrices (Mixed as) = Mixed $ map (\a -> a{aprice=Nothing}) as
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | 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.
 | 
				
			||||||
showMixedAmountOneLineWithoutPrice :: MixedAmount -> String
 | 
					-- With a True argument, adds ANSI codes to show negative amounts in red.
 | 
				
			||||||
showMixedAmountOneLineWithoutPrice m = intercalate ", " $ map showAmountWithoutPrice as
 | 
					showMixedAmountOneLineWithoutPrice :: Bool -> MixedAmount -> String
 | 
				
			||||||
    where
 | 
					showMixedAmountOneLineWithoutPrice c m =
 | 
				
			||||||
      (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
					  intercalate ", " $ map (showAmountWithoutPrice c) as
 | 
				
			||||||
      stripPrices (Mixed as) = Mixed $ map stripprice as where stripprice a = a{aprice=Nothing}
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Colour version.
 | 
					 | 
				
			||||||
cshowMixedAmountOneLineWithoutPrice :: MixedAmount -> String
 | 
					 | 
				
			||||||
cshowMixedAmountOneLineWithoutPrice m = intercalate ", " $ map cshowAmountWithoutPrice as
 | 
					 | 
				
			||||||
    where
 | 
					    where
 | 
				
			||||||
      (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
					      (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
				
			||||||
      stripPrices (Mixed as) = Mixed $ map stripprice as where stripprice a = a{aprice=Nothing}
 | 
					      stripPrices (Mixed as) = Mixed $ map stripprice as where stripprice a = a{aprice=Nothing}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Like showMixedAmountOneLineWithoutPrice, but show at most two commodities,
 | 
					-- | Like showMixedAmountOneLineWithoutPrice, but show at most two commodities,
 | 
				
			||||||
-- with a elision indicator if there are more.
 | 
					-- with a elision indicator if there are more.
 | 
				
			||||||
showMixedAmountElided :: MixedAmount -> String
 | 
					-- With a True argument, adds ANSI codes to show negative amounts in red.
 | 
				
			||||||
showMixedAmountElided m = intercalate ", " $ take 2 astrs ++ elisionstr
 | 
					showMixedAmountElided :: Bool -> MixedAmount -> String
 | 
				
			||||||
 | 
					showMixedAmountElided c m = intercalate ", " $ take 2 astrs ++ elisionstr
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    astrs = map showAmountWithoutPrice as
 | 
					    astrs = map (showAmountWithoutPrice c) as
 | 
				
			||||||
      where
 | 
					 | 
				
			||||||
        (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
					 | 
				
			||||||
          where
 | 
					 | 
				
			||||||
            stripPrices (Mixed as) = Mixed $ map stripprice as
 | 
					 | 
				
			||||||
              where
 | 
					 | 
				
			||||||
                stripprice a = a{aprice=Nothing}
 | 
					 | 
				
			||||||
    elisionstr | n > 2     = [show (n - 2) ++ " more.."]
 | 
					 | 
				
			||||||
               | otherwise = []
 | 
					 | 
				
			||||||
      where
 | 
					 | 
				
			||||||
        n = length astrs
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Colour version.
 | 
					 | 
				
			||||||
cshowMixedAmountElided :: MixedAmount -> String
 | 
					 | 
				
			||||||
cshowMixedAmountElided m = intercalate ", " $ take 2 astrs ++ elisionstr
 | 
					 | 
				
			||||||
  where
 | 
					 | 
				
			||||||
    astrs = map cshowAmountWithoutPrice as
 | 
					 | 
				
			||||||
      where
 | 
					      where
 | 
				
			||||||
        (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
					        (Mixed as) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
 | 
				
			||||||
          where
 | 
					          where
 | 
				
			||||||
@ -846,8 +815,8 @@ tests_Amount = tests "Amount" [
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
    ,test "showMixedAmountWithoutPrice" $ do
 | 
					    ,test "showMixedAmountWithoutPrice" $ do
 | 
				
			||||||
      let a = usd 1 `at` eur 2
 | 
					      let a = usd 1 `at` eur 2
 | 
				
			||||||
      showMixedAmountWithoutPrice (Mixed [a]) @?= "$1.00"
 | 
					      showMixedAmountWithoutPrice False (Mixed [a]) @?= "$1.00"
 | 
				
			||||||
      showMixedAmountWithoutPrice (Mixed [a, -a]) @?= "0"
 | 
					      showMixedAmountWithoutPrice False (Mixed [a, -a]) @?= "0"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    ,tests "normaliseMixedAmount" [
 | 
					    ,tests "normaliseMixedAmount" [
 | 
				
			||||||
       test "a missing amount overrides any other amounts" $
 | 
					       test "a missing amount overrides any other amounts" $
 | 
				
			||||||
 | 
				
			|||||||
@ -263,7 +263,7 @@ budgetReportAsText ropts@ReportOpts{..} budgetr =
 | 
				
			|||||||
    budgetwidth = maximum' $ map snd amountsAndGoals
 | 
					    budgetwidth = maximum' $ map snd amountsAndGoals
 | 
				
			||||||
    amountsAndGoals = map (\(a,g) -> (amountLength a, amountLength g))
 | 
					    amountsAndGoals = map (\(a,g) -> (amountLength a, amountLength g))
 | 
				
			||||||
                    . concatMap prrAmounts $ prRows budgetr
 | 
					                    . concatMap prrAmounts $ prRows budgetr
 | 
				
			||||||
      where amountLength = maybe 0 (length . showMixedAmountOneLineWithoutPrice)
 | 
					      where amountLength = maybe 0 (length . showMixedAmountOneLineWithoutPrice False)
 | 
				
			||||||
    -- XXX lay out actual, percentage and/or goal in the single table cell for now, should probably use separate cells
 | 
					    -- XXX lay out actual, percentage and/or goal in the single table cell for now, should probably use separate cells
 | 
				
			||||||
    showcell :: BudgetCell -> String
 | 
					    showcell :: BudgetCell -> String
 | 
				
			||||||
    showcell (mactual, mbudget) = actualstr ++ " " ++ budgetstr
 | 
					    showcell (mactual, mbudget) = actualstr ++ " " ++ budgetstr
 | 
				
			||||||
@ -296,12 +296,10 @@ budgetReportAsText ropts@ReportOpts{..} budgetr =
 | 
				
			|||||||
               Nothing
 | 
					               Nothing
 | 
				
			||||||
      where
 | 
					      where
 | 
				
			||||||
        maybecost = if valuationTypeIsCost ropts then mixedAmountCost else id
 | 
					        maybecost = if valuationTypeIsCost ropts then mixedAmountCost else id
 | 
				
			||||||
    showamt :: MixedAmount -> String
 | 
					    showamt = showMixedAmountOneLineWithoutPrice color_
 | 
				
			||||||
    showamt | color_    = cshowMixedAmountOneLineWithoutPrice
 | 
					 | 
				
			||||||
            | otherwise = showMixedAmountOneLineWithoutPrice
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
    -- don't show the budget amount in color, it messes up alignment
 | 
					    -- don't show the budget amount in color, it messes up alignment (XXX)
 | 
				
			||||||
    showbudgetamt = showMixedAmountOneLineWithoutPrice
 | 
					    showbudgetamt = showMixedAmountOneLineWithoutPrice False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    maybetranspose | transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals)
 | 
					    maybetranspose | transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals)
 | 
				
			||||||
                   | otherwise  = id
 | 
					                   | otherwise  = id
 | 
				
			||||||
 | 
				
			|||||||
@ -108,7 +108,7 @@ asInit d reset ui@UIState{
 | 
				
			|||||||
      AccountsScreenItem{asItemIndentLevel        = indent
 | 
					      AccountsScreenItem{asItemIndentLevel        = indent
 | 
				
			||||||
                        ,asItemAccountName        = fullacct
 | 
					                        ,asItemAccountName        = fullacct
 | 
				
			||||||
                        ,asItemDisplayAccountName = replaceHiddenAccountsNameWith "All" $ if tree_ ropts' then shortacct else fullacct
 | 
					                        ,asItemDisplayAccountName = replaceHiddenAccountsNameWith "All" $ if tree_ ropts' then shortacct else fullacct
 | 
				
			||||||
                        ,asItemRenderedAmounts    = map showAmountWithoutPrice amts -- like showMixedAmountOneLineWithoutPrice
 | 
					                        ,asItemRenderedAmounts    = map (showAmountWithoutPrice False) amts
 | 
				
			||||||
                        }
 | 
					                        }
 | 
				
			||||||
      where
 | 
					      where
 | 
				
			||||||
        Mixed amts = normaliseMixedAmountSquashPricesForDisplay $ stripPrices bal
 | 
					        Mixed amts = normaliseMixedAmountSquashPricesForDisplay $ stripPrices bal
 | 
				
			||||||
 | 
				
			|||||||
@ -95,8 +95,8 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportopts_=ropts
 | 
				
			|||||||
                                                     [s] -> s
 | 
					                                                     [s] -> s
 | 
				
			||||||
                                                     ss  -> intercalate ", " ss
 | 
					                                                     ss  -> intercalate ", " ss
 | 
				
			||||||
                                                     -- _   -> "<split>"  -- should do this if accounts field width < 30
 | 
					                                                     -- _   -> "<split>"  -- should do this if accounts field width < 30
 | 
				
			||||||
                            ,rsItemChangeAmount  = showMixedAmountOneLineWithoutPrice change
 | 
					                            ,rsItemChangeAmount  = showMixedAmountOneLineWithoutPrice False change
 | 
				
			||||||
                            ,rsItemBalanceAmount = showMixedAmountOneLineWithoutPrice bal
 | 
					                            ,rsItemBalanceAmount = showMixedAmountOneLineWithoutPrice False bal
 | 
				
			||||||
                            ,rsItemTransaction   = t
 | 
					                            ,rsItemTransaction   = t
 | 
				
			||||||
                            }
 | 
					                            }
 | 
				
			||||||
    -- 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
 | 
				
			||||||
 | 
				
			|||||||
@ -102,7 +102,7 @@ accountOnlyQuery = ("inacctonly:" <>) . quoteIfSpaced
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
mixedAmountAsHtml :: MixedAmount -> HtmlUrl a
 | 
					mixedAmountAsHtml :: MixedAmount -> HtmlUrl a
 | 
				
			||||||
mixedAmountAsHtml b _ =
 | 
					mixedAmountAsHtml b _ =
 | 
				
			||||||
  for_ (lines (showMixedAmountWithoutPrice b)) $ \t -> do
 | 
					  for_ (lines (showMixedAmountWithoutPrice False b)) $ \t -> do
 | 
				
			||||||
    H.span ! A.class_ c $ toHtml t
 | 
					    H.span ! A.class_ c $ toHtml t
 | 
				
			||||||
    H.br
 | 
					    H.br
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
 | 
				
			|||||||
@ -349,11 +349,11 @@ balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts@ReportOpts{..}} j = do
 | 
				
			|||||||
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
 | 
					balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
 | 
				
			||||||
balanceReportAsCsv opts (items, total) =
 | 
					balanceReportAsCsv opts (items, total) =
 | 
				
			||||||
  ["account","balance"] :
 | 
					  ["account","balance"] :
 | 
				
			||||||
  [[T.unpack a, showMixedAmountOneLineWithoutPrice b] | (a, _, _, b) <- items]
 | 
					  [[T.unpack a, showMixedAmountOneLineWithoutPrice False b] | (a, _, _, b) <- items]
 | 
				
			||||||
  ++
 | 
					  ++
 | 
				
			||||||
  if no_total_ opts
 | 
					  if no_total_ opts
 | 
				
			||||||
  then []
 | 
					  then []
 | 
				
			||||||
  else [["total", showMixedAmountOneLineWithoutPrice total]]
 | 
					  else [["total", showMixedAmountOneLineWithoutPrice False total]]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Render a single-column balance report as plain text.
 | 
					-- | Render a single-column balance report as plain text.
 | 
				
			||||||
balanceReportAsText :: ReportOpts -> BalanceReport -> String
 | 
					balanceReportAsText :: ReportOpts -> BalanceReport -> String
 | 
				
			||||||
@ -426,10 +426,7 @@ renderComponent opts (acctname, depth, total) (FormatField ljust min max field)
 | 
				
			|||||||
                                 Just m  -> depth * m
 | 
					                                 Just m  -> depth * m
 | 
				
			||||||
                                 Nothing -> depth
 | 
					                                 Nothing -> depth
 | 
				
			||||||
  AccountField     -> formatString ljust min max (T.unpack acctname)
 | 
					  AccountField     -> formatString ljust min max (T.unpack acctname)
 | 
				
			||||||
  TotalField       -> fitStringMulti min max True False $ showamt total
 | 
					  TotalField       -> fitStringMulti min max True False $ showMixedAmountWithoutPrice (color_ opts) total
 | 
				
			||||||
    where
 | 
					 | 
				
			||||||
      showamt | color_ opts = cshowMixedAmountWithoutPrice
 | 
					 | 
				
			||||||
              | otherwise   = showMixedAmountWithoutPrice
 | 
					 | 
				
			||||||
  _                -> ""
 | 
					  _                -> ""
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Render one StringFormat component for a balance report item.
 | 
					-- | Render one StringFormat component for a balance report item.
 | 
				
			||||||
@ -446,8 +443,7 @@ renderComponent1 opts (acctname, depth, total) (FormatField ljust min max field)
 | 
				
			|||||||
                        indented = ((replicate (depth*2) ' ')++)
 | 
					                        indented = ((replicate (depth*2) ' ')++)
 | 
				
			||||||
  TotalField       -> fitStringMulti min max True False $ ((intercalate ", " . map strip . lines) (showamt total))
 | 
					  TotalField       -> fitStringMulti min max True False $ ((intercalate ", " . map strip . lines) (showamt total))
 | 
				
			||||||
    where
 | 
					    where
 | 
				
			||||||
      showamt | color_ opts = cshowMixedAmountWithoutPrice
 | 
					      showamt = showMixedAmountWithoutPrice (color_ opts)
 | 
				
			||||||
              | otherwise   = showMixedAmountWithoutPrice
 | 
					 | 
				
			||||||
  _                -> ""
 | 
					  _                -> ""
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- rendering multi-column balance reports
 | 
					-- rendering multi-column balance reports
 | 
				
			||||||
@ -464,7 +460,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
 | 
				
			|||||||
   ++ ["Average" | average_]
 | 
					   ++ ["Average" | average_]
 | 
				
			||||||
  ) :
 | 
					  ) :
 | 
				
			||||||
  [T.unpack (displayFull a) :
 | 
					  [T.unpack (displayFull a) :
 | 
				
			||||||
   map showMixedAmountOneLineWithoutPrice
 | 
					   map (showMixedAmountOneLineWithoutPrice False)
 | 
				
			||||||
   (amts
 | 
					   (amts
 | 
				
			||||||
    ++ [rowtot | row_total_]
 | 
					    ++ [rowtot | row_total_]
 | 
				
			||||||
    ++ [rowavg | average_])
 | 
					    ++ [rowavg | average_])
 | 
				
			||||||
@ -473,7 +469,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
 | 
				
			|||||||
  if no_total_ opts
 | 
					  if no_total_ opts
 | 
				
			||||||
  then []
 | 
					  then []
 | 
				
			||||||
  else ["Total:" :
 | 
					  else ["Total:" :
 | 
				
			||||||
        map showMixedAmountOneLineWithoutPrice (
 | 
					        map (showMixedAmountOneLineWithoutPrice False) (
 | 
				
			||||||
          coltotals
 | 
					          coltotals
 | 
				
			||||||
          ++ [tot | row_total_]
 | 
					          ++ [tot | row_total_]
 | 
				
			||||||
          ++ [avg | average_]
 | 
					          ++ [avg | average_]
 | 
				
			||||||
@ -635,10 +631,8 @@ balanceReportTableAsText :: ReportOpts -> Table String String MixedAmount -> Str
 | 
				
			|||||||
balanceReportTableAsText ropts@ReportOpts{..} = tableAsText ropts showamt
 | 
					balanceReportTableAsText ropts@ReportOpts{..} = tableAsText ropts showamt
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    showamt
 | 
					    showamt
 | 
				
			||||||
      | no_elide_ && color_ = cshowMixedAmountOneLineWithoutPrice
 | 
					      | no_elide_ = showMixedAmountOneLineWithoutPrice color_
 | 
				
			||||||
      | no_elide_           =  showMixedAmountOneLineWithoutPrice
 | 
					      | otherwise = showMixedAmountElided color_
 | 
				
			||||||
      | color_              = cshowMixedAmountElided
 | 
					 | 
				
			||||||
      | otherwise           =  showMixedAmountElided
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
tests_Balance = tests "Balance" [
 | 
					tests_Balance = tests "Balance" [
 | 
				
			||||||
 | 
				
			|||||||
@ -86,8 +86,8 @@ postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,code,desc,acct,amt,bal
 | 
				
			|||||||
                             BalancedVirtualPosting -> (\s -> "["++s++"]")
 | 
					                             BalancedVirtualPosting -> (\s -> "["++s++"]")
 | 
				
			||||||
                             VirtualPosting -> (\s -> "("++s++")")
 | 
					                             VirtualPosting -> (\s -> "("++s++")")
 | 
				
			||||||
                             _ -> id
 | 
					                             _ -> id
 | 
				
			||||||
    amt = showMixedAmountOneLineWithoutPrice $ pamount p
 | 
					    amt = showMixedAmountOneLineWithoutPrice False $ pamount p
 | 
				
			||||||
    bal = showMixedAmountOneLineWithoutPrice b
 | 
					    bal = showMixedAmountOneLineWithoutPrice False 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 -> String
 | 
					postingsReportAsText :: CliOpts -> PostingsReport -> String
 | 
				
			||||||
@ -179,8 +179,7 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
 | 
				
			|||||||
              BalancedVirtualPosting -> (\s -> "["++s++"]", acctwidth-2)
 | 
					              BalancedVirtualPosting -> (\s -> "["++s++"]", acctwidth-2)
 | 
				
			||||||
              VirtualPosting         -> (\s -> "("++s++")", acctwidth-2)
 | 
					              VirtualPosting         -> (\s -> "("++s++")", acctwidth-2)
 | 
				
			||||||
              _                      -> (id,acctwidth)
 | 
					              _                      -> (id,acctwidth)
 | 
				
			||||||
      showamt | color_ (reportopts_ opts) = cshowMixedAmountWithoutPrice
 | 
					      showamt = showMixedAmountWithoutPrice (color_ $ reportopts_ opts)
 | 
				
			||||||
              | otherwise                 = showMixedAmountWithoutPrice
 | 
					 | 
				
			||||||
      amt = showamt $ pamount p
 | 
					      amt = showamt $ pamount p
 | 
				
			||||||
      bal = showamt b
 | 
					      bal = showamt b
 | 
				
			||||||
      -- alternate behaviour, show null amounts as 0 instead of blank
 | 
					      -- alternate behaviour, show null amounts as 0 instead of blank
 | 
				
			||||||
 | 
				
			|||||||
@ -262,7 +262,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 showMixedAmountOneLineWithoutPrice (
 | 
					           map (showMixedAmountOneLineWithoutPrice False) (
 | 
				
			||||||
             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 =
 | 
				
			|||||||
                  in
 | 
					                  in
 | 
				
			||||||
                    [tr_ $ mconcat $
 | 
					                    [tr_ $ mconcat $
 | 
				
			||||||
                         th_ [class_ "", style_ "text-align:left"] "Net:"
 | 
					                         th_ [class_ "", style_ "text-align:left"] "Net:"
 | 
				
			||||||
                       : [th_ [class_ "amount coltotal", defstyle] (toHtml $ showMixedAmountOneLineWithoutPrice a) | a <- coltotals]
 | 
					                       : [th_ [class_ "amount coltotal", defstyle] (toHtml $ showMixedAmountOneLineWithoutPrice False a) | a <- coltotals]
 | 
				
			||||||
                      ++ (if row_total_ ropts then [th_ [class_ "amount coltotal", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice $ grandtotal] else [])
 | 
					                      ++ (if row_total_ ropts then [th_ [class_ "amount coltotal", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice False grandtotal] else [])
 | 
				
			||||||
                      ++ (if average_ ropts   then [th_ [class_ "amount colaverage", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice $ grandavg] else [])
 | 
					                      ++ (if average_ ropts   then [th_ [class_ "amount colaverage", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice False grandavg] else [])
 | 
				
			||||||
                    ]
 | 
					                    ]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  in do
 | 
					  in do
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user