2008-10-01 04:29:58 +04:00
{- |
2011-08-31 21:22:53 +04:00
A simple 'Amount' is some quantity of money , shares , or anything else .
2016-05-08 02:18:04 +03:00
It has a ( possibly null ) 'CommoditySymbol' and a numeric quantity :
2007-03-13 07:11:39 +03:00
2008-10-01 13:33:05 +04:00
@
2014-09-11 00:07:53 +04:00
$ 1
2007-03-13 07:11:39 +03:00
£ - 50
2014-09-11 00:07:53 +04:00
EUR 3.44
2007-03-13 07:11:39 +03:00
GOOG 500
1.5 h
2009-12-13 00:10:39 +03:00
90 apples
2014-09-11 00:07:53 +04:00
0
2008-10-01 13:33:05 +04:00
@
2007-03-13 07:11:39 +03:00
2011-08-31 21:22:53 +04:00
It may also have an assigned 'Price' , representing this amount's per - unit
or total cost in a different commodity . If present , this is rendered like
so :
2007-03-13 07:11:39 +03:00
2008-10-01 13:33:05 +04:00
@
2011-08-31 21:22:53 +04:00
EUR 2 \@ $ 1.50 ( unit price )
EUR 2 \@\@ $ 3 ( total price )
2008-10-01 13:33:05 +04:00
@
2007-03-13 07:11:39 +03:00
2011-08-31 21:22:53 +04:00
A 'MixedAmount' is zero or more simple amounts , so can represent multiple
2011-08-30 17:16:30 +04:00
commodities ; this is the type most often used :
2009-11-25 16:31:08 +03:00
@
2011-08-30 17:16:30 +04:00
0
2009-12-13 00:10:39 +03:00
$ 50 + EUR 3
16 h + $ 13.55 + AAPL 500 + 6 oranges
2008-10-01 13:33:05 +04:00
@
2009-11-25 16:31:08 +03:00
2011-08-30 17:16:30 +04:00
When a mixed amount has been \ " normalised \ " , it has no more than one amount
in each commodity and no zero amounts ; or it has just a single zero amount
and no others .
2011-08-31 21:22:53 +04:00
Limited arithmetic with simple and mixed amounts is supported , best used
with similar amounts since it mostly ignores assigned prices and commodity
exchange rates .
2009-11-25 16:31:08 +03:00
2007-03-13 07:11:39 +03:00
- }
2019-12-29 02:52:32 +03:00
-- Silence safe 0.3.18's deprecation warnings for (max|min)imum(By)?Def for now
-- (may hide other deprecation warnings too). https://github.com/ndmitchell/safe/issues/26
{- # OPTIONS_GHC - Wno - warnings - deprecations # -}
2018-07-31 11:30:08 +03:00
{- # LANGUAGE StandaloneDeriving, RecordWildCards, OverloadedStrings # -}
lib: textification: commodity symbols
hledger -f data/100x100x10.journal stats
<<ghc: 39288536 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.016 MUT (0.028 elapsed), 0.009 GC (0.012 elapsed) :ghc>>
<<ghc: 39290808 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.003 elapsed), 0.015 MUT (0.021 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
<<ghc: 314268960 bytes, 612 GCs, 2143219/6826152 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.009 elapsed), 0.135 MUT (0.151 elapsed), 0.065 GC (0.178 elapsed) :ghc>>
<<ghc: 314254512 bytes, 612 GCs, 2072377/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.130 MUT (0.134 elapsed), 0.064 GC (0.075 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
<<ghc: 3070016592 bytes, 5965 GCs, 13138220/64266016 avg/max bytes residency (10 samples), 128M in use, 0.000 INIT (0.000 elapsed), 1.272 MUT (1.322 elapsed), 0.527 GC (0.595 elapsed) :ghc>>
<<ghc: 3069989896 bytes, 5973 GCs, 12687877/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.295 MUT (1.324 elapsed), 0.511 GC (0.570 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
<<ghc: 30753448072 bytes, 59763 GCs, 121502982/673169248 avg/max bytes residency (14 samples), 1640M in use, 0.000 INIT (0.007 elapsed), 12.421 MUT (12.672 elapsed), 6.240 GC (7.812 elapsed) :ghc>>
<<ghc: 30753350528 bytes, 59811 GCs, 117616668/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.001 INIT (0.011 elapsed), 13.209 MUT (13.683 elapsed), 6.137 GC (7.117 elapsed) :ghc>>
2016-05-24 05:13:43 +03:00
2010-12-27 23:26:22 +03:00
module Hledger.Data.Amount (
2011-08-31 20:54:10 +04:00
-- * Amount
2012-11-20 01:20:10 +04:00
amount ,
2011-08-31 20:54:10 +04:00
nullamt ,
2012-05-27 22:14:20 +04:00
missingamt ,
2012-11-20 06:22:20 +04:00
num ,
2012-11-20 01:20:10 +04:00
usd ,
eur ,
gbp ,
2019-11-11 23:06:58 +03:00
per ,
2012-11-20 01:20:10 +04:00
hrs ,
at ,
( @@ ) ,
2011-09-02 04:42:41 +04:00
amountWithCommodity ,
2011-08-31 20:54:10 +04:00
-- ** arithmetic
2020-06-01 01:48:08 +03:00
amountCost ,
2020-05-30 04:57:22 +03:00
amountIsZero ,
amountLooksZero ,
2011-08-31 20:54:10 +04:00
divideAmount ,
2018-07-17 01:36:06 +03:00
multiplyAmount ,
2018-11-14 04:43:15 +03:00
divideAmountAndPrice ,
multiplyAmountAndPrice ,
2018-11-14 02:37:42 +03:00
amountTotalPriceToUnitPrice ,
2011-08-31 20:54:10 +04:00
-- ** rendering
2012-11-20 01:20:10 +04:00
amountstyle ,
2018-04-20 22:18:28 +03:00
styleAmount ,
2019-10-20 17:08:45 +03:00
styleAmountExceptPrecision ,
2011-08-31 20:54:10 +04:00
showAmount ,
2017-04-26 04:34:09 +03:00
cshowAmount ,
2014-07-28 17:32:09 +04:00
showAmountWithZeroCommodity ,
2011-08-31 20:54:10 +04:00
showAmountDebug ,
showAmountWithoutPrice ,
maxprecision ,
maxprecisionwithpoint ,
2012-11-20 01:20:10 +04:00
setAmountPrecision ,
withPrecision ,
2019-01-17 01:45:50 +03:00
setFullPrecision ,
2019-06-15 04:32:00 +03:00
setNaturalPrecision ,
2019-06-15 04:32:45 +03:00
setNaturalPrecisionUpTo ,
2018-08-04 18:44:50 +03:00
setAmountInternalPrecision ,
withInternalPrecision ,
setAmountDecimalPoint ,
withDecimalPoint ,
2012-11-20 01:20:10 +04:00
canonicaliseAmount ,
2011-08-31 20:54:10 +04:00
-- * MixedAmount
nullmixedamt ,
2012-05-27 22:14:20 +04:00
missingmixedamt ,
2012-11-20 03:17:55 +04:00
mixed ,
2011-08-31 20:54:10 +04:00
amounts ,
2014-07-02 18:35:06 +04:00
filterMixedAmount ,
2014-07-19 03:45:46 +04:00
filterMixedAmountByCommodity ,
2020-01-21 04:09:07 +03:00
mapMixedAmount ,
2014-07-28 17:32:09 +04:00
normaliseMixedAmountSquashPricesForDisplay ,
normaliseMixedAmount ,
2020-06-24 16:38:17 +03:00
unifyMixedAmount ,
2020-01-22 22:57:42 +03:00
mixedAmountStripPrices ,
2011-08-31 20:54:10 +04:00
-- ** arithmetic
2020-06-01 01:48:08 +03:00
mixedAmountCost ,
2011-08-31 20:54:10 +04:00
divideMixedAmount ,
2018-07-17 01:36:06 +03:00
multiplyMixedAmount ,
2018-11-14 04:43:15 +03:00
divideMixedAmountAndPrice ,
multiplyMixedAmountAndPrice ,
2014-12-26 22:04:23 +03:00
averageMixedAmounts ,
2016-12-10 18:04:48 +03:00
isNegativeAmount ,
2011-08-31 20:54:10 +04:00
isNegativeMixedAmount ,
2020-05-30 04:57:22 +03:00
mixedAmountIsZero ,
mixedAmountLooksZero ,
2018-11-14 02:37:42 +03:00
mixedAmountTotalPriceToUnitPrice ,
2011-08-31 20:54:10 +04:00
-- ** rendering
2018-04-20 22:18:28 +03:00
styleMixedAmount ,
2011-08-31 20:54:10 +04:00
showMixedAmount ,
2015-10-30 04:05:02 +03:00
showMixedAmountOneLine ,
2011-08-31 20:54:10 +04:00
showMixedAmountDebug ,
showMixedAmountWithoutPrice ,
2014-07-28 17:32:09 +04:00
showMixedAmountOneLineWithoutPrice ,
2020-06-26 22:14:49 +03:00
showMixedAmountElided ,
2017-04-26 04:34:09 +03:00
cshowMixedAmountWithoutPrice ,
cshowMixedAmountOneLineWithoutPrice ,
2020-06-26 22:14:49 +03:00
cshowMixedAmountElided ,
2014-07-28 17:32:09 +04:00
showMixedAmountWithZeroCommodity ,
2011-08-31 20:54:10 +04:00
showMixedAmountWithPrecision ,
2012-11-20 01:20:10 +04:00
setMixedAmountPrecision ,
canonicaliseMixedAmount ,
2011-08-31 20:54:10 +04:00
-- * misc.
2012-11-12 20:31:43 +04:00
ltraceamount ,
2018-09-06 23:08:26 +03:00
tests_Amount
2011-08-31 20:54:10 +04:00
) where
2020-06-24 16:38:17 +03:00
import Control.Monad ( foldM )
2011-05-28 08:11:44 +04:00
import Data.Char ( isDigit )
2019-01-17 01:45:50 +03:00
import Data.Decimal ( roundTo , decimalPlaces , normalizeDecimal )
2014-07-28 17:32:09 +04:00
import Data.Function ( on )
2011-05-28 08:11:44 +04:00
import Data.List
2019-06-02 01:28:10 +03:00
import qualified Data.Map as M
2010-11-15 02:29:04 +03:00
import Data.Map ( findWithDefault )
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
import Data.Maybe
lib: textification: commodity symbols
hledger -f data/100x100x10.journal stats
<<ghc: 39288536 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.016 MUT (0.028 elapsed), 0.009 GC (0.012 elapsed) :ghc>>
<<ghc: 39290808 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.003 elapsed), 0.015 MUT (0.021 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
<<ghc: 314268960 bytes, 612 GCs, 2143219/6826152 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.009 elapsed), 0.135 MUT (0.151 elapsed), 0.065 GC (0.178 elapsed) :ghc>>
<<ghc: 314254512 bytes, 612 GCs, 2072377/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.130 MUT (0.134 elapsed), 0.064 GC (0.075 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
<<ghc: 3070016592 bytes, 5965 GCs, 13138220/64266016 avg/max bytes residency (10 samples), 128M in use, 0.000 INIT (0.000 elapsed), 1.272 MUT (1.322 elapsed), 0.527 GC (0.595 elapsed) :ghc>>
<<ghc: 3069989896 bytes, 5973 GCs, 12687877/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.295 MUT (1.324 elapsed), 0.511 GC (0.570 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
<<ghc: 30753448072 bytes, 59763 GCs, 121502982/673169248 avg/max bytes residency (14 samples), 1640M in use, 0.000 INIT (0.007 elapsed), 12.421 MUT (12.672 elapsed), 6.240 GC (7.812 elapsed) :ghc>>
<<ghc: 30753350528 bytes, 59811 GCs, 117616668/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.001 INIT (0.011 elapsed), 13.209 MUT (13.683 elapsed), 6.137 GC (7.117 elapsed) :ghc>>
2016-05-24 05:13:43 +03:00
import qualified Data.Text as T
2018-02-16 13:26:39 +03:00
import Safe ( maximumDef )
2011-05-28 08:11:44 +04:00
import Text.Printf
2010-11-15 02:29:04 +03:00
2010-05-20 03:08:53 +04:00
import Hledger.Data.Types
import Hledger.Data.Commodity
2019-07-15 13:28:52 +03:00
import Hledger.Utils
2008-10-01 04:29:58 +04:00
2008-10-10 05:53:39 +04:00
2015-08-10 02:20:02 +03:00
deriving instance Show MarketPrice
2007-07-04 05:38:56 +04:00
2018-04-20 22:18:28 +03:00
-------------------------------------------------------------------------------
-- Amount styles
2019-07-15 13:28:52 +03:00
-- | Default amount style
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
amountstyle = AmountStyle L False 0 ( Just '.' ) Nothing
2012-11-20 01:20:10 +04:00
2018-04-20 22:18:28 +03:00
2011-08-31 20:54:10 +04:00
-------------------------------------------------------------------------------
-- Amount
2008-10-18 12:39:08 +04:00
instance Num Amount where
2012-11-20 01:20:10 +04:00
abs a @ Amount { aquantity = q } = a { aquantity = abs q }
signum a @ Amount { aquantity = q } = a { aquantity = signum q }
fromInteger i = nullamt { aquantity = fromInteger i }
2018-02-16 04:28:23 +03:00
negate a @ Amount { aquantity = q } = a { aquantity = - q }
2012-11-20 01:20:10 +04:00
( + ) = similarAmountsOp ( + )
( - ) = similarAmountsOp ( - )
( * ) = similarAmountsOp ( * )
2008-10-18 12:39:08 +04:00
2011-08-31 20:54:10 +04:00
-- | The empty simple amount.
2012-11-20 02:39:08 +04:00
amount , nullamt :: Amount
2019-06-08 00:23:19 +03:00
amount = Amount { acommodity = " " , aquantity = 0 , aprice = Nothing , astyle = amountstyle , aismultiplier = False }
2012-11-20 01:20:10 +04:00
nullamt = amount
2014-07-28 17:32:09 +04:00
-- | A temporary value for parsed transactions which had no amount specified.
missingamt :: Amount
missingamt = amount { acommodity = " AUTO " }
2015-02-27 16:23:07 +03:00
-- Handy amount constructors for tests.
-- usd/eur/gbp round their argument to a whole number of pennies/cents.
2012-11-20 06:22:20 +04:00
num n = amount { acommodity = " " , aquantity = n }
2015-02-27 16:27:24 +03:00
hrs n = amount { acommodity = " h " , aquantity = n , astyle = amountstyle { asprecision = 2 , ascommodityside = R } }
2014-10-18 23:09:43 +04:00
usd n = amount { acommodity = " $ " , aquantity = roundTo 2 n , astyle = amountstyle { asprecision = 2 } }
eur n = amount { acommodity = " € " , aquantity = roundTo 2 n , astyle = amountstyle { asprecision = 2 } }
gbp n = amount { acommodity = " £ " , aquantity = roundTo 2 n , astyle = amountstyle { asprecision = 2 } }
2019-11-11 23:06:58 +03:00
per n = amount { acommodity = " % " , aquantity = n , astyle = amountstyle { asprecision = 1 , ascommodityside = R , ascommodityspaced = True } }
2019-06-08 00:23:19 +03:00
amt ` at ` priceamt = amt { aprice = Just $ UnitPrice priceamt }
amt @@ priceamt = amt { aprice = Just $ TotalPrice priceamt }
2012-11-20 01:20:10 +04:00
2014-07-28 17:32:09 +04:00
-- | Apply a binary arithmetic operator to two amounts, which should
-- be in the same commodity if non-zero (warning, this is not checked).
-- A zero result keeps the commodity of the second amount.
-- The result's display style is that of the second amount, with
-- precision set to the highest of either amount.
-- Prices are ignored and discarded.
2014-10-18 21:45:17 +04:00
-- Remember: the caller is responsible for ensuring both amounts have the same commodity.
2014-10-18 23:09:43 +04:00
similarAmountsOp :: ( Quantity -> Quantity -> Quantity ) -> Amount -> Amount -> Amount
2014-07-28 17:32:09 +04:00
similarAmountsOp op Amount { acommodity = _ , aquantity = q1 , astyle = AmountStyle { asprecision = p1 } }
Amount { acommodity = c2 , aquantity = q2 , astyle = s2 @ AmountStyle { asprecision = p2 } } =
-- trace ("a1:"++showAmountDebug a1) $ trace ("a2:"++showAmountDebug a2) $ traceWith (("= :"++).showAmountDebug)
amount { acommodity = c2 , aquantity = q1 ` op ` q2 , astyle = s2 { asprecision = max p1 p2 } }
2014-09-11 00:07:53 +04:00
-- c1==c2 || q1==0 || q2==0 =
2012-11-20 03:36:36 +04:00
-- otherwise = error "tried to do simple arithmetic with amounts in different commodities"
2011-04-22 17:44:08 +04:00
2011-08-31 20:54:10 +04:00
-- | Convert an amount to the specified commodity, ignoring and discarding
-- any assigned prices and assuming an exchange rate of 1.
2016-05-08 02:18:04 +03:00
amountWithCommodity :: CommoditySymbol -> Amount -> Amount
2019-06-08 00:23:19 +03:00
amountWithCommodity c a = a { acommodity = c , aprice = Nothing }
2010-02-04 19:40:30 +03:00
2020-06-01 01:48:08 +03:00
-- | Convert a amount to its "cost" or "selling price" in another commodity,
-- using its attached transaction price if it has one. Notes:
2011-08-31 21:44:31 +04:00
--
2020-06-01 01:48:08 +03:00
-- - price amounts must be MixedAmounts with exactly one component Amount
-- (or there will be a runtime error XXX)
2011-08-31 21:44:31 +04:00
--
2020-06-01 01:48:08 +03:00
-- - price amounts should be positive
-- (though this is currently not enforced)
amountCost :: Amount -> Amount
amountCost a @ Amount { aquantity = q , aprice = mp } =
2019-06-08 00:23:19 +03:00
case mp of
Nothing -> a
Just ( UnitPrice p @ Amount { aquantity = pq } ) -> p { aquantity = pq * q }
Just ( TotalPrice p @ Amount { aquantity = pq } ) -> p { aquantity = pq * signum q }
2008-10-15 05:06:05 +04:00
2018-11-14 02:37:42 +03:00
-- | Replace an amount's TotalPrice, if it has one, with an equivalent UnitPrice.
-- Has no effect on amounts without one.
-- Also increases the unit price's display precision to show one extra decimal place,
2019-07-15 13:28:52 +03:00
-- to help keep transaction amounts balancing.
2018-11-14 02:37:42 +03:00
-- Does Decimal division, might be some rounding/irrational number issues.
amountTotalPriceToUnitPrice :: Amount -> Amount
2019-07-15 13:28:52 +03:00
amountTotalPriceToUnitPrice
2019-06-08 00:23:19 +03:00
a @ Amount { aquantity = q , aprice = Just ( TotalPrice pa @ Amount { aquantity = pq , astyle = ps @ AmountStyle { asprecision = pp } } ) }
= a { aprice = Just $ UnitPrice pa { aquantity = abs ( pq / q ) , astyle = ps { asprecision = pp + 1 } } }
2018-11-14 02:37:42 +03:00
amountTotalPriceToUnitPrice a = a
2011-08-31 20:54:10 +04:00
-- | Divide an amount's quantity by a constant.
2018-11-14 04:25:32 +03:00
divideAmount :: Quantity -> Amount -> Amount
divideAmount n a @ Amount { aquantity = q } = a { aquantity = q / n }
2011-08-31 20:54:10 +04:00
2018-07-17 01:36:06 +03:00
-- | Multiply an amount's quantity by a constant.
2018-11-14 04:25:32 +03:00
multiplyAmount :: Quantity -> Amount -> Amount
multiplyAmount n a @ Amount { aquantity = q } = a { aquantity = q * n }
2018-07-17 01:36:06 +03:00
2018-11-14 04:43:15 +03:00
-- | Divide an amount's quantity (and its total price, if it has one) by a constant.
-- The total price will be kept positive regardless of the multiplier's sign.
divideAmountAndPrice :: Quantity -> Amount -> Amount
2019-06-08 00:23:19 +03:00
divideAmountAndPrice n a @ Amount { aquantity = q , aprice = p } = a { aquantity = q / n , aprice = f <$> p }
2018-11-14 04:43:15 +03:00
where
f ( TotalPrice a ) = TotalPrice $ abs $ n ` divideAmount ` a
f p = p
-- | Multiply an amount's quantity (and its total price, if it has one) by a constant.
-- The total price will be kept positive regardless of the multiplier's sign.
multiplyAmountAndPrice :: Quantity -> Amount -> Amount
2019-06-08 00:23:19 +03:00
multiplyAmountAndPrice n a @ Amount { aquantity = q , aprice = p } = a { aquantity = q * n , aprice = f <$> p }
2018-11-14 04:43:15 +03:00
where
f ( TotalPrice a ) = TotalPrice $ abs $ n ` multiplyAmount ` a
f p = p
2011-08-31 20:54:10 +04:00
-- | Is this amount negative ? The price is ignored.
isNegativeAmount :: Amount -> Bool
2012-11-20 01:20:10 +04:00
isNegativeAmount Amount { aquantity = q } = q < 0
2011-08-31 20:54:10 +04:00
2012-11-14 21:25:02 +04:00
digits = " 123456789 " :: String
2020-05-30 04:57:22 +03:00
-- | Does mixed amount appear to be zero when rendered with its
-- display precision ?
amountLooksZero :: Amount -> Bool
amountLooksZero = not . any ( ` elem ` digits ) . showAmountWithoutPriceOrCommodity
2011-08-31 20:54:10 +04:00
2020-05-30 04:57:22 +03:00
-- | Is this amount exactly zero, ignoring its display precision ?
amountIsZero :: Amount -> Bool
amountIsZero Amount { aquantity = q } = q == 0
2011-08-31 20:54:10 +04:00
2010-11-13 18:10:06 +03:00
-- | Get the string representation of an amount, based on its commodity's
-- display settings except using the specified precision.
showAmountWithPrecision :: Int -> Amount -> String
showAmountWithPrecision p = showAmount . setAmountPrecision p
2012-11-20 01:20:10 +04:00
-- | Set an amount's display precision, flipped.
withPrecision :: Amount -> Int -> Amount
withPrecision = flip setAmountPrecision
2010-11-13 18:10:06 +03:00
2019-12-01 03:56:45 +03:00
-- | Set an amount's display precision.
setAmountPrecision :: Int -> Amount -> Amount
setAmountPrecision p a @ Amount { astyle = s } = a { astyle = s { asprecision = p } }
-- | Increase an amount's display precision, if needed, to enough
-- decimal places to show it exactly (showing all significant decimal
-- digits, excluding trailing zeros).
2019-01-17 01:45:50 +03:00
setFullPrecision :: Amount -> Amount
setFullPrecision a = setAmountPrecision p a
where
2020-01-21 04:09:07 +03:00
p = max displayprecision naturalprecision
2019-01-17 01:45:50 +03:00
displayprecision = asprecision $ astyle a
2020-01-21 04:09:07 +03:00
naturalprecision = fromIntegral $ decimalPlaces $ normalizeDecimal $ aquantity a
2019-01-17 01:45:50 +03:00
2019-12-01 03:56:45 +03:00
-- | Set an amount's display precision to just enough decimal places
-- to show it exactly (possibly less than the number specified by
-- the amount's display style).
2019-06-15 04:32:00 +03:00
setNaturalPrecision :: Amount -> Amount
setNaturalPrecision a = setAmountPrecision normalprecision a
2019-01-17 01:45:50 +03:00
where
normalprecision = fromIntegral $ decimalPlaces $ normalizeDecimal $ aquantity a
2019-12-01 03:56:45 +03:00
-- | Set an amount's display precision to just enough decimal places
-- to show it exactly (possibly less than the number specified by the
-- amount's display style), but not more than the given maximum number
-- of decimal digits.
2019-06-15 04:32:45 +03:00
setNaturalPrecisionUpTo :: Int -> Amount -> Amount
setNaturalPrecisionUpTo n a = setAmountPrecision ( min n normalprecision ) a
where
normalprecision = fromIntegral $ decimalPlaces $ normalizeDecimal $ aquantity a
2013-12-07 01:51:19 +04:00
-- | Get a string representation of an amount for debugging,
-- appropriate to the current debug level. 9 shows maximum detail.
2010-03-07 00:47:10 +03:00
showAmountDebug :: Amount -> String
2012-11-20 01:20:10 +04:00
showAmountDebug Amount { acommodity = " AUTO " } = " (missing) "
2019-06-04 03:26:27 +03:00
showAmountDebug Amount { .. } = printf " Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s} " ( show acommodity ) ( show aquantity ) ( showAmountPriceDebug aprice ) ( show astyle )
2010-03-07 00:47:10 +03:00
2009-11-25 15:57:30 +03:00
-- | Get the string representation of an amount, without any \@ price.
2009-11-25 15:19:02 +03:00
showAmountWithoutPrice :: Amount -> String
2019-06-08 00:23:19 +03:00
showAmountWithoutPrice a = showAmount a { aprice = Nothing }
2009-11-25 15:19:02 +03:00
2019-07-15 13:28:52 +03:00
-- | Set an amount's internal precision, ie rounds the Decimal representing
2018-08-04 18:44:50 +03:00
-- the amount's quantity to some number of decimal places.
-- Rounding is done with Data.Decimal's default roundTo function:
-- "If the value ends in 5 then it is rounded to the nearest even value (Banker's Rounding)".
-- Does not change the amount's display precision.
2019-07-15 13:28:52 +03:00
-- Intended only for internal use, eg when comparing amounts in tests.
2018-08-04 18:44:50 +03:00
setAmountInternalPrecision :: Int -> Amount -> Amount
2019-07-15 13:28:52 +03:00
setAmountInternalPrecision p a @ Amount { aquantity = q , astyle = s } = a {
astyle = s { asprecision = p }
2018-08-04 18:44:50 +03:00
, aquantity = roundTo ( fromIntegral p ) q
}
-- | Set an amount's internal precision, flipped.
2019-07-15 13:28:52 +03:00
-- Intended only for internal use, eg when comparing amounts in tests.
2018-08-04 18:44:50 +03:00
withInternalPrecision :: Amount -> Int -> Amount
withInternalPrecision = flip setAmountInternalPrecision
-- | Set (or clear) an amount's display decimal point.
setAmountDecimalPoint :: Maybe Char -> Amount -> Amount
setAmountDecimalPoint mc a @ Amount { astyle = s } = a { astyle = s { asdecimalpoint = mc } }
-- | Set (or clear) an amount's display decimal point, flipped.
withDecimalPoint :: Amount -> Maybe Char -> Amount
withDecimalPoint = flip setAmountDecimalPoint
2017-04-26 04:34:09 +03:00
-- | Colour version.
cshowAmountWithoutPrice :: Amount -> String
2019-06-08 00:23:19 +03:00
cshowAmountWithoutPrice a = cshowAmount a { aprice = Nothing }
2017-04-26 04:34:09 +03:00
2010-11-15 01:44:37 +03:00
-- | Get the string representation of an amount, without any price or commodity symbol.
showAmountWithoutPriceOrCommodity :: Amount -> String
2019-06-08 00:23:19 +03:00
showAmountWithoutPriceOrCommodity a = showAmount a { acommodity = " " , aprice = Nothing }
2010-11-15 01:44:37 +03:00
2019-06-08 00:23:19 +03:00
showAmountPrice :: Maybe AmountPrice -> String
showAmountPrice Nothing = " "
showAmountPrice ( Just ( UnitPrice pa ) ) = " @ " ++ showAmount pa
showAmountPrice ( Just ( TotalPrice pa ) ) = " @@ " ++ showAmount pa
2011-04-22 17:40:55 +04:00
2019-06-08 00:23:19 +03:00
showAmountPriceDebug :: Maybe AmountPrice -> String
showAmountPriceDebug Nothing = " "
showAmountPriceDebug ( Just ( UnitPrice pa ) ) = " @ " ++ showAmountDebug pa
showAmountPriceDebug ( Just ( TotalPrice pa ) ) = " @@ " ++ showAmountDebug pa
2011-04-22 17:40:55 +04:00
2020-06-01 01:48:08 +03:00
-- | Given a map of standard commodity display styles, apply the
-- appropriate one to this amount. If there's no standard style for
-- this amount's commodity, return the amount unchanged.
2018-04-20 22:18:28 +03:00
styleAmount :: M . Map CommoditySymbol AmountStyle -> Amount -> Amount
styleAmount styles a =
case M . lookup ( acommodity a ) styles of
Just s -> a { astyle = s }
2019-07-15 13:28:52 +03:00
Nothing -> a
2018-04-20 22:18:28 +03:00
2019-10-20 17:08:45 +03:00
-- | Like styleAmount, but keep the number of decimal places unchanged.
styleAmountExceptPrecision :: M . Map CommoditySymbol AmountStyle -> Amount -> Amount
styleAmountExceptPrecision styles a @ Amount { astyle = AmountStyle { asprecision = origp } } =
case M . lookup ( acommodity a ) styles of
Just s -> a { astyle = s { asprecision = origp } }
Nothing -> a
2014-07-28 17:32:09 +04:00
-- | Get the string representation of an amount, based on its
-- commodity's display settings. String representations equivalent to
-- zero are converted to just \"0\". The special "missing" amount is
-- displayed as the empty string.
2011-04-22 17:40:55 +04:00
showAmount :: Amount -> String
2014-07-28 17:32:09 +04:00
showAmount = showAmountHelper False
2019-07-15 13:28:52 +03:00
-- | Colour version. For a negative amount, adds ANSI codes to change the colour,
2017-04-26 04:34:09 +03:00
-- currently to hard-coded red.
cshowAmount :: Amount -> String
cshowAmount a =
( if isNegativeAmount a then color Dull Red else id ) $
showAmountHelper False a
2014-07-28 17:32:09 +04:00
showAmountHelper :: Bool -> Amount -> String
showAmountHelper _ Amount { acommodity = " AUTO " } = " "
2019-06-08 00:23:19 +03:00
showAmountHelper showzerocommodity a @ Amount { acommodity = c , aprice = mp , astyle = AmountStyle { .. } } =
2012-11-20 01:20:10 +04:00
case ascommodityside of
lib: textification: commodity symbols
hledger -f data/100x100x10.journal stats
<<ghc: 39288536 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.016 MUT (0.028 elapsed), 0.009 GC (0.012 elapsed) :ghc>>
<<ghc: 39290808 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.003 elapsed), 0.015 MUT (0.021 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
<<ghc: 314268960 bytes, 612 GCs, 2143219/6826152 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.009 elapsed), 0.135 MUT (0.151 elapsed), 0.065 GC (0.178 elapsed) :ghc>>
<<ghc: 314254512 bytes, 612 GCs, 2072377/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.130 MUT (0.134 elapsed), 0.064 GC (0.075 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
<<ghc: 3070016592 bytes, 5965 GCs, 13138220/64266016 avg/max bytes residency (10 samples), 128M in use, 0.000 INIT (0.000 elapsed), 1.272 MUT (1.322 elapsed), 0.527 GC (0.595 elapsed) :ghc>>
<<ghc: 3069989896 bytes, 5973 GCs, 12687877/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.295 MUT (1.324 elapsed), 0.511 GC (0.570 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
<<ghc: 30753448072 bytes, 59763 GCs, 121502982/673169248 avg/max bytes residency (14 samples), 1640M in use, 0.000 INIT (0.007 elapsed), 12.421 MUT (12.672 elapsed), 6.240 GC (7.812 elapsed) :ghc>>
<<ghc: 30753350528 bytes, 59811 GCs, 117616668/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.001 INIT (0.011 elapsed), 13.209 MUT (13.683 elapsed), 6.137 GC (7.117 elapsed) :ghc>>
2016-05-24 05:13:43 +03:00
L -> printf " %s%s%s%s " ( T . unpack c' ) space quantity' price
R -> printf " %s%s%s%s " quantity' space ( T . unpack c' ) price
2011-04-22 17:40:55 +04:00
where
quantity = showamountquantity a
2018-02-16 04:28:23 +03:00
displayingzero = not ( any ( ` elem ` digits ) quantity )
2014-07-28 17:32:09 +04:00
( quantity' , c' ) | displayingzero && not showzerocommodity = ( " 0 " , " " )
| otherwise = ( quantity , quoteCommoditySymbolIfNeeded c )
2018-02-16 04:28:23 +03:00
space = if not ( T . null c' ) && ascommodityspaced then " " else " " :: String
2019-06-08 00:23:19 +03:00
price = showAmountPrice mp
2011-04-22 17:40:55 +04:00
2014-07-28 17:32:09 +04:00
-- | Like showAmount, but show a zero amount's commodity if it has one.
showAmountWithZeroCommodity :: Amount -> String
showAmountWithZeroCommodity = showAmountHelper True
2010-11-13 18:10:06 +03:00
-- | Get the string representation of the number part of of an amount,
2011-01-19 15:32:18 +03:00
-- using the display settings from its commodity.
2011-04-22 17:40:55 +04:00
showamountquantity :: Amount -> String
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
showamountquantity Amount { aquantity = q , astyle = AmountStyle { asprecision = p , asdecimalpoint = mdec , asdigitgroups = mgrps } } =
2018-02-16 04:28:23 +03:00
punctuatenumber ( fromMaybe '.' mdec ) mgrps qstr
2011-01-19 15:32:18 +03:00
where
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- isint n = fromIntegral (round n) == n
qstr -- p == maxprecision && isint q = printf "%d" (round q::Integer)
2014-10-18 23:09:43 +04:00
| p == maxprecisionwithpoint = show q
| p == maxprecision = chopdotzero $ show q
| otherwise = show $ roundTo ( fromIntegral p ) q
2011-01-20 03:17:32 +03:00
2019-09-28 03:23:33 +03:00
-- | Replace a number string's decimal mark with the specified
-- character, and add the specified digit group marks. The last digit
-- group will be repeated as needed.
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
punctuatenumber :: Char -> Maybe DigitGroupStyle -> String -> String
punctuatenumber dec mgrps s = sign ++ reverse ( applyDigitGroupStyle mgrps ( reverse int ) ) ++ frac''
2011-01-19 15:32:18 +03:00
where
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
( sign , num ) = break isDigit s
2011-01-19 15:32:18 +03:00
( int , frac ) = break ( == '.' ) num
frac' = dropWhile ( == '.' ) frac
frac'' | null frac' = " "
| otherwise = dec : frac'
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
applyDigitGroupStyle :: Maybe DigitGroupStyle -> String -> String
applyDigitGroupStyle Nothing s = s
applyDigitGroupStyle ( Just ( DigitGroups c gs ) ) s = addseps ( repeatLast gs ) s
where
addseps [] s = s
addseps ( g : gs ) s
| length s <= g = s
| otherwise = let ( part , rest ) = splitAt g s
in part ++ [ c ] ++ addseps gs rest
repeatLast [] = []
repeatLast gs = init gs ++ repeat ( last gs )
2011-01-19 15:32:18 +03:00
2011-08-31 20:54:10 +04:00
chopdotzero str = reverse $ case reverse str of
'0' : '.' : s -> s
s -> s
2007-07-04 05:38:56 +04:00
2011-08-31 20:54:10 +04:00
-- | For rendering: a special precision value which means show all available digits.
maxprecision :: Int
maxprecision = 999998
2009-05-17 02:54:12 +04:00
2011-08-31 20:54:10 +04:00
-- | For rendering: a special precision value which forces display of a decimal point.
maxprecisionwithpoint :: Int
maxprecisionwithpoint = 999999
2007-03-13 07:11:39 +03:00
2012-11-20 01:20:10 +04:00
-- like journalCanonicaliseAmounts
-- | Canonicalise an amount's display style using the provided commodity style map.
2016-05-08 02:18:04 +03:00
canonicaliseAmount :: M . Map CommoditySymbol AmountStyle -> Amount -> Amount
2012-11-20 01:20:10 +04:00
canonicaliseAmount styles a @ Amount { acommodity = c , astyle = s } = a { astyle = s' }
2011-08-31 20:54:10 +04:00
where
2012-11-20 01:20:10 +04:00
s' = findWithDefault s c styles
2011-08-31 20:54:10 +04:00
-------------------------------------------------------------------------------
-- MixedAmount
instance Num MixedAmount where
2012-11-20 01:20:10 +04:00
fromInteger i = Mixed [ fromInteger i ]
2011-08-31 20:54:10 +04:00
negate ( Mixed as ) = Mixed $ map negate as
2014-07-28 17:32:09 +04:00
( + ) ( Mixed as ) ( Mixed bs ) = normaliseMixedAmount $ Mixed $ as ++ bs
( * ) = error ' " e r r o r , m i x e d a m o u n t s d o n o t s u p p o r t m u l t i p l i c a t i o n "
abs = error ' " e r r o r , m i x e d a m o u n t s d o n o t s u p p o r t a b s "
signum = error ' " e r r o r , m i x e d a m o u n t s d o n o t s u p p o r t s i g n u m "
2011-08-31 20:54:10 +04:00
-- | The empty mixed amount.
nullmixedamt :: MixedAmount
nullmixedamt = Mixed []
-- | A temporary value for parsed transactions which had no amount specified.
2012-05-27 22:14:20 +04:00
missingmixedamt :: MixedAmount
missingmixedamt = Mixed [ missingamt ]
2014-07-28 17:32:09 +04:00
-- | Convert amounts in various commodities into a normalised MixedAmount.
mixed :: [ Amount ] -> MixedAmount
mixed = normaliseMixedAmount . Mixed
2012-11-12 20:31:43 +04:00
2014-07-28 17:32:09 +04:00
-- | Simplify a mixed amount's component amounts:
--
-- * amounts in the same commodity are combined unless they have different prices or total prices
--
balance, etc: fix amount style loss (fixes #230, #276)
hledger-lib-0.24's "track the commodity of zero amounts when
possible (useful eg for hledger-web's multi-commodity charts)" preserved
the commodity when normalising a zero mixed amount, but not the amount
style. This showed up as occasionally incorrect amount style (commodity
symbol placement, decimal point character, etc.) in balance reports with
certain journals, like this:
$ hledger bal
€3000.00 a <------ not using the canonical € style
4000,58€ 1
-1000,58€ D
-3000,00€ e
--------------------
0
I thought this would require a big rewrite of amount arithmetic, but it
seems that just being a little more careful is enough. When normalising
a mixed amount containing multiple zeros in the same commodity, we now
preserve the last zero with its amount style, instead of replacing them
all with a new one.
2015-09-03 02:09:49 +03:00
-- * multiple zero amounts, all with the same non-null commodity, are replaced by just the last of them, preserving the commodity and amount style (all but the last zero amount are discarded)
2014-07-28 17:32:09 +04:00
--
balance, etc: fix amount style loss (fixes #230, #276)
hledger-lib-0.24's "track the commodity of zero amounts when
possible (useful eg for hledger-web's multi-commodity charts)" preserved
the commodity when normalising a zero mixed amount, but not the amount
style. This showed up as occasionally incorrect amount style (commodity
symbol placement, decimal point character, etc.) in balance reports with
certain journals, like this:
$ hledger bal
€3000.00 a <------ not using the canonical € style
4000,58€ 1
-1000,58€ D
-3000,00€ e
--------------------
0
I thought this would require a big rewrite of amount arithmetic, but it
seems that just being a little more careful is enough. When normalising
a mixed amount containing multiple zeros in the same commodity, we now
preserve the last zero with its amount style, instead of replacing them
all with a new one.
2015-09-03 02:09:49 +03:00
-- * multiple zero amounts with multiple commodities, or no commodities, are replaced by one commodity-less zero amount
--
-- * an empty amount list is replaced by one commodity-less zero amount
2014-07-28 17:32:09 +04:00
--
-- * the special "missing" mixed amount remains unchanged
--
normaliseMixedAmount :: MixedAmount -> MixedAmount
normaliseMixedAmount = normaliseHelper False
normaliseHelper :: Bool -> MixedAmount -> MixedAmount
normaliseHelper squashprices ( Mixed as )
| missingamt ` elem ` as = missingmixedamt -- missingamt should always be alone, but detect it even if not
| null nonzeros = Mixed [ newzero ]
| otherwise = Mixed nonzeros
where
newzero = case filter ( /= " " ) ( map acommodity zeros ) of
balance, etc: fix amount style loss (fixes #230, #276)
hledger-lib-0.24's "track the commodity of zero amounts when
possible (useful eg for hledger-web's multi-commodity charts)" preserved
the commodity when normalising a zero mixed amount, but not the amount
style. This showed up as occasionally incorrect amount style (commodity
symbol placement, decimal point character, etc.) in balance reports with
certain journals, like this:
$ hledger bal
€3000.00 a <------ not using the canonical € style
4000,58€ 1
-1000,58€ D
-3000,00€ e
--------------------
0
I thought this would require a big rewrite of amount arithmetic, but it
seems that just being a little more careful is enough. When normalising
a mixed amount containing multiple zeros in the same commodity, we now
preserve the last zero with its amount style, instead of replacing them
all with a new one.
2015-09-03 02:09:49 +03:00
_ : _ -> last zeros
2014-07-28 17:32:09 +04:00
_ -> nullamt
2020-05-30 04:57:22 +03:00
( zeros , nonzeros ) = partition amountIsZero $
2014-07-28 17:32:09 +04:00
map sumSimilarAmountsUsingFirstPrice $
groupBy groupfn $
2018-02-16 04:28:23 +03:00
sortBy sortfn
2014-07-28 17:32:09 +04:00
as
sortfn | squashprices = compare ` on ` acommodity
| otherwise = compare ` on ` \ a -> ( acommodity a , aprice a )
groupfn | squashprices = ( == ) ` on ` acommodity
| otherwise = \ a1 a2 -> acommodity a1 == acommodity a2 && combinableprices a1 a2
2019-06-08 00:23:19 +03:00
combinableprices Amount { aprice = Nothing } Amount { aprice = Nothing } = True
combinableprices Amount { aprice = Just ( UnitPrice p1 ) } Amount { aprice = Just ( UnitPrice p2 ) } = p1 == p2
2014-07-28 17:32:09 +04:00
combinableprices _ _ = False
-- | Like normaliseMixedAmount, but combine each commodity's amounts
-- into just one by throwing away all prices except the first. This is
-- only used as a rendering helper, and could show a misleading price.
normaliseMixedAmountSquashPricesForDisplay :: MixedAmount -> MixedAmount
normaliseMixedAmountSquashPricesForDisplay = normaliseHelper True
2020-06-24 16:38:17 +03:00
-- | Unify a MixedAmount to a single commodity value if possible.
-- Like normaliseMixedAmount, this consolidates amounts of the same commodity
-- and discards zero amounts; but this one insists on simplifying to
-- a single commodity, and will return Nothing if this is not possible.
unifyMixedAmount :: MixedAmount -> Maybe Amount
unifyMixedAmount = foldM combine 0 . amounts
where
combine amount result
| amountIsZero amount = Just result
| amountIsZero result = Just amount
| acommodity amount == acommodity result = Just $ amount + result
| otherwise = Nothing
2014-07-28 17:32:09 +04:00
-- | Sum same-commodity amounts in a lossy way, applying the first
-- price to the result and discarding any other prices. Only used as a
-- rendering helper.
sumSimilarAmountsUsingFirstPrice :: [ Amount ] -> Amount
sumSimilarAmountsUsingFirstPrice [] = nullamt
2017-01-13 03:24:53 +03:00
sumSimilarAmountsUsingFirstPrice as = ( sumStrict as ) { aprice = aprice $ head as }
2014-07-28 17:32:09 +04:00
2016-08-03 19:29:22 +03:00
-- -- | Sum same-commodity amounts. If there were different prices, set
-- -- the price to a special marker indicating "various". Only used as a
-- -- rendering helper.
2014-07-28 17:32:09 +04:00
-- sumSimilarAmountsNotingPriceDifference :: [Amount] -> Amount
-- sumSimilarAmountsNotingPriceDifference [] = nullamt
-- sumSimilarAmountsNotingPriceDifference as = undefined
2010-07-28 03:20:20 +04:00
2011-08-30 17:16:30 +04:00
-- | Get a mixed amount's component amounts.
2008-10-19 00:27:25 +04:00
amounts :: MixedAmount -> [ Amount ]
amounts ( Mixed as ) = as
2014-07-02 18:35:06 +04:00
-- | Filter a mixed amount's component amounts by a predicate.
filterMixedAmount :: ( Amount -> Bool ) -> MixedAmount -> MixedAmount
filterMixedAmount p ( Mixed as ) = Mixed $ filter p as
2014-07-19 03:45:46 +04:00
-- | Return an unnormalised MixedAmount containing exactly one Amount
-- with the specified commodity and the quantity of that commodity
-- found in the original. NB if Amount's quantity is zero it will be
-- discarded next time the MixedAmount gets normalised.
2016-05-08 02:18:04 +03:00
filterMixedAmountByCommodity :: CommoditySymbol -> MixedAmount -> MixedAmount
2014-07-19 03:45:46 +04:00
filterMixedAmountByCommodity c ( Mixed as ) = Mixed as'
where
as' = case filter ( ( == c ) . acommodity ) as of
[] -> [ nullamt { acommodity = c } ]
as'' -> [ sum as'' ]
2018-11-14 04:25:32 +03:00
-- | Apply a transform to a mixed amount's component 'Amount's.
mapMixedAmount :: ( Amount -> Amount ) -> MixedAmount -> MixedAmount
mapMixedAmount f ( Mixed as ) = Mixed $ map f as
2020-06-01 01:48:08 +03:00
-- | Convert all component amounts to cost/selling price where
-- possible (see amountCost).
mixedAmountCost :: MixedAmount -> MixedAmount
mixedAmountCost ( Mixed as ) = Mixed $ map amountCost as
2019-05-23 22:15:54 +03:00
2011-08-31 20:54:10 +04:00
-- | Divide a mixed amount's quantities by a constant.
2018-11-14 04:25:32 +03:00
divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount
divideMixedAmount n = mapMixedAmount ( divideAmount n )
2011-08-31 20:54:10 +04:00
2018-07-17 01:36:06 +03:00
-- | Multiply a mixed amount's quantities by a constant.
2018-11-14 04:25:32 +03:00
multiplyMixedAmount :: Quantity -> MixedAmount -> MixedAmount
multiplyMixedAmount n = mapMixedAmount ( multiplyAmount n )
2018-07-17 01:36:06 +03:00
2018-11-14 04:43:15 +03:00
-- | Divide a mixed amount's quantities (and total prices, if any) by a constant.
-- The total prices will be kept positive regardless of the multiplier's sign.
divideMixedAmountAndPrice :: Quantity -> MixedAmount -> MixedAmount
divideMixedAmountAndPrice n = mapMixedAmount ( divideAmountAndPrice n )
-- | Multiply a mixed amount's quantities (and total prices, if any) by a constant.
-- The total prices will be kept positive regardless of the multiplier's sign.
multiplyMixedAmountAndPrice :: Quantity -> MixedAmount -> MixedAmount
multiplyMixedAmountAndPrice n = mapMixedAmount ( multiplyAmountAndPrice n )
2014-12-26 22:04:23 +03:00
-- | Calculate the average of some mixed amounts.
averageMixedAmounts :: [ MixedAmount ] -> MixedAmount
averageMixedAmounts [] = 0
2019-07-15 13:28:52 +03:00
averageMixedAmounts as = fromIntegral ( length as ) ` divideMixedAmount ` sum as
2014-12-26 22:04:23 +03:00
2020-05-29 23:07:02 +03:00
-- | Is this mixed amount negative, if we can tell that unambiguously?
-- Ie when normalised, are all individual commodity amounts negative ?
2011-08-31 20:54:10 +04:00
isNegativeMixedAmount :: MixedAmount -> Maybe Bool
2020-05-29 23:07:02 +03:00
isNegativeMixedAmount m =
case amounts $ normaliseMixedAmountSquashPricesForDisplay m of
[] -> Just False
[ a ] -> Just $ isNegativeAmount a
as | all isNegativeAmount as -> Just True
2020-06-02 00:27:08 +03:00
as | not ( any isNegativeAmount as ) -> Just False
2020-05-29 23:07:02 +03:00
_ -> Nothing -- multiple amounts with different signs
2020-05-30 04:57:22 +03:00
-- | Does this mixed amount appear to be zero when rendered with its
-- display precision ?
mixedAmountLooksZero :: MixedAmount -> Bool
mixedAmountLooksZero = all amountLooksZero . amounts . normaliseMixedAmountSquashPricesForDisplay
2011-08-31 20:54:10 +04:00
2020-05-30 04:57:22 +03:00
-- | Is this mixed amount exactly zero, ignoring display precisions ?
mixedAmountIsZero :: MixedAmount -> Bool
mixedAmountIsZero = all amountIsZero . amounts . normaliseMixedAmountSquashPricesForDisplay
2010-02-27 21:06:29 +03:00
2011-08-31 20:54:10 +04:00
-- -- | MixedAmount derived Eq instance in Types.hs doesn't know that we
-- -- want $0 = EUR0 = 0. Yet we don't want to drag all this code over there.
-- -- For now, use this when cross-commodity zero equality is important.
2010-12-27 23:26:22 +03:00
-- mixedAmountEquals :: MixedAmount -> MixedAmount -> Bool
2020-05-30 04:57:22 +03:00
-- mixedAmountEquals a b = amounts a' == amounts b' || (mixedAmountLooksZero a' && mixedAmountLooksZero b')
2014-07-28 17:32:09 +04:00
-- where a' = normaliseMixedAmountSquashPricesForDisplay a
-- b' = normaliseMixedAmountSquashPricesForDisplay b
2009-01-17 21:07:20 +03:00
2020-06-01 01:48:08 +03:00
-- | Given a map of standard commodity display styles, apply the
-- appropriate one to each individual amount.
2018-04-20 22:18:28 +03:00
styleMixedAmount :: M . Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
2019-07-15 13:28:52 +03:00
styleMixedAmount styles ( Mixed as ) = Mixed $ map ( styleAmount styles ) as
2018-04-20 22:18:28 +03:00
2014-07-28 17:32:09 +04:00
-- | Get the string representation of a mixed amount, after
-- normalising it to one amount per commodity. Assumes amounts have
-- no or similar prices, otherwise this can show misleading prices.
2008-10-19 00:27:25 +04:00
showMixedAmount :: MixedAmount -> String
2015-10-30 04:05:02 +03:00
showMixedAmount = showMixedAmountHelper False False
2014-07-28 17:32:09 +04:00
-- | Like showMixedAmount, but zero amounts are shown with their
-- commodity if they have one.
showMixedAmountWithZeroCommodity :: MixedAmount -> String
2015-10-30 04:05:02 +03:00
showMixedAmountWithZeroCommodity = showMixedAmountHelper True False
2014-07-28 17:32:09 +04:00
2015-10-30 04:05:02 +03:00
-- | Get the one-line string representation of a mixed amount.
showMixedAmountOneLine :: MixedAmount -> String
showMixedAmountOneLine = showMixedAmountHelper False True
showMixedAmountHelper :: Bool -> Bool -> MixedAmount -> String
showMixedAmountHelper showzerocommodity useoneline m =
join $ map showamt $ amounts $ normaliseMixedAmountSquashPricesForDisplay m
2014-07-28 17:32:09 +04:00
where
2015-10-30 04:05:02 +03:00
join | useoneline = intercalate " , "
| otherwise = vConcatRightAligned
showamt | showzerocommodity = showAmountWithZeroCommodity
| otherwise = showAmount
2010-03-07 00:47:10 +03:00
2013-12-07 01:51:19 +04:00
-- | Compact labelled trace of a mixed amount, for debugging.
2012-11-12 20:31:43 +04:00
ltraceamount :: String -> MixedAmount -> MixedAmount
2013-12-07 01:51:19 +04:00
ltraceamount s = traceWith ( ( ( s ++ " : " ) ++ ) . showMixedAmount )
2012-11-12 20:31:43 +04:00
2011-08-30 17:16:30 +04:00
-- | Set the display precision in the amount's commodities.
2011-01-20 02:27:11 +03:00
setMixedAmountPrecision :: Int -> MixedAmount -> MixedAmount
setMixedAmountPrecision p ( Mixed as ) = Mixed $ map ( setAmountPrecision p ) as
2010-11-13 18:10:06 +03:00
-- | Get the string representation of a mixed amount, showing each of its
-- component amounts with the specified precision, ignoring their
2011-08-31 21:44:31 +04:00
-- commoditys' display precision settings.
2010-11-13 18:10:06 +03:00
showMixedAmountWithPrecision :: Int -> MixedAmount -> String
showMixedAmountWithPrecision p m =
2014-07-28 17:32:09 +04:00
vConcatRightAligned $ map ( showAmountWithPrecision p ) $ amounts $ normaliseMixedAmountSquashPricesForDisplay m
2010-11-13 18:10:06 +03:00
2010-03-07 00:47:10 +03:00
-- | Get an unambiguous string representation of a mixed amount for debugging.
showMixedAmountDebug :: MixedAmount -> String
2012-05-27 22:14:20 +04:00
showMixedAmountDebug m | m == missingmixedamt = " (missing) "
| otherwise = printf " Mixed [%s] " as
2014-07-28 17:32:09 +04:00
where as = intercalate " \ n " $ map showAmountDebug $ amounts m
2008-10-15 06:11:30 +04:00
2018-02-16 13:26:39 +03:00
-- TODO these and related fns are comically complicated:
-- | Get the string representation of a mixed amount, without showing any transaction prices.
2009-11-25 15:19:02 +03:00
showMixedAmountWithoutPrice :: MixedAmount -> String
2018-02-16 13:26:39 +03:00
showMixedAmountWithoutPrice m = intercalate " \ n " $ map showamt as
where
Mixed as = normaliseMixedAmountSquashPricesForDisplay $ mixedAmountStripPrices m
showamt = printf ( printf " %%%ds " width ) . showAmountWithoutPrice
where
width = maximumDef 0 $ map ( length . showAmount ) as
2009-11-25 15:19:02 +03:00
2018-02-16 13:26:39 +03:00
-- | Colour version of showMixedAmountWithoutPrice. Any individual Amount
-- which is negative is wrapped in ANSI codes to make it display in red.
2017-04-26 04:34:09 +03:00
cshowMixedAmountWithoutPrice :: MixedAmount -> String
2018-02-16 13:26:39 +03:00
cshowMixedAmountWithoutPrice m = intercalate " \ n " $ map showamt as
where
Mixed as = normaliseMixedAmountSquashPricesForDisplay $ mixedAmountStripPrices m
showamt a =
( if isNegativeAmount a then color Dull Red else id ) $
printf ( printf " %%%ds " width ) $ showAmountWithoutPrice a
where
width = maximumDef 0 $ map ( length . showAmount ) as
mixedAmountStripPrices :: MixedAmount -> MixedAmount
2019-06-08 00:23:19 +03:00
mixedAmountStripPrices ( Mixed as ) = Mixed $ map ( \ a -> a { aprice = Nothing } ) as
2018-02-16 04:28:23 +03:00
2014-07-03 18:45:55 +04:00
-- | Get the one-line string representation of a mixed amount, but without
-- any \@ prices.
showMixedAmountOneLineWithoutPrice :: MixedAmount -> String
2018-02-16 04:28:23 +03:00
showMixedAmountOneLineWithoutPrice m = intercalate " , " $ map showAmountWithoutPrice as
2014-07-03 18:45:55 +04:00
where
2014-07-28 17:32:09 +04:00
( Mixed as ) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
2019-06-08 00:23:19 +03:00
stripPrices ( Mixed as ) = Mixed $ map stripprice as where stripprice a = a { aprice = Nothing }
2014-07-03 18:45:55 +04:00
2017-04-26 04:34:09 +03:00
-- | Colour version.
cshowMixedAmountOneLineWithoutPrice :: MixedAmount -> String
2018-02-16 04:28:23 +03:00
cshowMixedAmountOneLineWithoutPrice m = intercalate " , " $ map cshowAmountWithoutPrice as
2017-04-26 04:34:09 +03:00
where
( Mixed as ) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
2019-06-08 00:23:19 +03:00
stripPrices ( Mixed as ) = Mixed $ map stripprice as where stripprice a = a { aprice = Nothing }
2017-04-26 04:34:09 +03:00
2020-06-26 22:14:49 +03:00
-- | Like showMixedAmountOneLineWithoutPrice, but show at most two commodities,
-- with a elision indicator if there are more.
showMixedAmountElided :: MixedAmount -> String
showMixedAmountElided m = intercalate " , " $ take 2 astrs ++ elisionstr
where
astrs = map showAmountWithoutPrice 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
( 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
2012-11-20 01:20:10 +04:00
-- | Canonicalise a mixed amount's display styles using the provided commodity style map.
2016-05-08 02:18:04 +03:00
canonicaliseMixedAmount :: M . Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
2012-11-20 01:20:10 +04:00
canonicaliseMixedAmount styles ( Mixed as ) = Mixed $ map ( canonicaliseAmount styles ) as
2018-11-14 02:37:42 +03:00
-- | Replace each component amount's TotalPrice, if it has one, with an equivalent UnitPrice.
2019-07-15 13:28:52 +03:00
-- Has no effect on amounts without one.
2018-11-14 02:37:42 +03:00
-- Does Decimal division, might be some rounding/irrational number issues.
mixedAmountTotalPriceToUnitPrice :: MixedAmount -> MixedAmount
mixedAmountTotalPriceToUnitPrice ( Mixed as ) = Mixed $ map amountTotalPriceToUnitPrice as
2018-04-20 22:18:28 +03:00
2011-08-31 20:54:10 +04:00
-------------------------------------------------------------------------------
2018-09-04 20:01:26 +03:00
-- tests
2018-09-06 23:08:26 +03:00
tests_Amount = tests " Amount " [
2018-09-04 20:01:26 +03:00
tests " Amount " [
2020-06-01 01:48:08 +03:00
test " amountCost " $ do
amountCost ( eur 1 ) @?= eur 1
amountCost ( eur 2 ) { aprice = Just $ UnitPrice $ usd 2 } @?= usd 4
amountCost ( eur 1 ) { aprice = Just $ TotalPrice $ usd 2 } @?= usd 2
amountCost ( eur ( - 1 ) ) { aprice = Just $ TotalPrice $ usd 2 } @?= usd ( - 2 )
2019-11-27 23:46:29 +03:00
2020-05-30 04:57:22 +03:00
, test " amountLooksZero " $ do
assertBool " " $ amountLooksZero amount
assertBool " " $ amountLooksZero $ usd 0
2019-11-27 23:46:29 +03:00
2019-11-29 02:29:03 +03:00
, test " negating amounts " $ do
2019-11-27 23:46:29 +03:00
negate ( usd 1 ) @?= ( usd 1 ) { aquantity = - 1 }
let b = ( usd 1 ) { aprice = Just $ UnitPrice $ eur 2 } in negate b @?= b { aquantity = - 1 }
2019-11-29 02:29:03 +03:00
, test " adding amounts without prices " $ do
2019-11-27 23:46:29 +03:00
( usd 1.23 + usd ( - 1.23 ) ) @?= usd 0
( usd 1.23 + usd ( - 1.23 ) ) @?= usd 0
( usd ( - 1.23 ) + usd ( - 1.23 ) ) @?= usd ( - 2.46 )
sum [ usd 1.23 , usd ( - 1.23 ) , usd ( - 1.23 ) , - ( usd ( - 1.23 ) ) ] @?= usd 0
-- highest precision is preserved
asprecision ( astyle $ sum [ usd 1 ` withPrecision ` 1 , usd 1 ` withPrecision ` 3 ] ) @?= 3
asprecision ( astyle $ sum [ usd 1 ` withPrecision ` 3 , usd 1 ` withPrecision ` 1 ] ) @?= 3
-- adding different commodities assumes conversion rate 1
2020-05-30 04:57:22 +03:00
assertBool " " $ amountLooksZero ( usd 1.23 - eur 1.23 )
2019-11-27 23:46:29 +03:00
2019-11-29 02:29:03 +03:00
, test " showAmount " $ do
2019-11-27 23:46:29 +03:00
showAmount ( usd 0 + gbp 0 ) @?= " 0 "
2011-04-22 17:40:55 +04:00
2010-03-09 07:03:51 +03:00
]
2018-09-04 20:01:26 +03:00
, tests " MixedAmount " [
2019-11-29 02:29:03 +03:00
test " adding mixed amounts to zero, the commodity and amount style are preserved " $
2018-09-04 20:01:26 +03:00
sum ( map ( Mixed . ( : [] ) )
[ usd 1.25
, usd ( - 1 ) ` withPrecision ` 3
, usd ( - 0.25 )
] )
2019-11-27 23:46:29 +03:00
@?= Mixed [ usd 0 ` withPrecision ` 3 ]
2019-07-15 13:28:52 +03:00
2019-11-29 02:29:03 +03:00
, test " adding mixed amounts with total prices " $ do
2018-09-04 20:01:26 +03:00
sum ( map ( Mixed . ( : [] ) )
[ usd 1 @@ eur 1
, usd ( - 2 ) @@ eur 1
] )
2019-11-27 23:46:29 +03:00
@?= Mixed [ usd 1 @@ eur 1
2018-09-04 20:01:26 +03:00
, usd ( - 2 ) @@ eur 1
]
2019-07-15 13:28:52 +03:00
2019-11-29 02:29:03 +03:00
, test " showMixedAmount " $ do
2019-11-27 23:46:29 +03:00
showMixedAmount ( Mixed [ usd 1 ] ) @?= " $1.00 "
showMixedAmount ( Mixed [ usd 1 ` at ` eur 2 ] ) @?= " $1.00 @ €2.00 "
showMixedAmount ( Mixed [ usd 0 ] ) @?= " 0 "
showMixedAmount ( Mixed [] ) @?= " 0 "
showMixedAmount missingmixedamt @?= " "
2019-07-15 13:28:52 +03:00
2019-11-29 02:29:03 +03:00
, test " showMixedAmountWithoutPrice " $ do
2019-11-27 23:46:29 +03:00
let a = usd 1 ` at ` eur 2
showMixedAmountWithoutPrice ( Mixed [ a ] ) @?= " $1.00 "
showMixedAmountWithoutPrice ( Mixed [ a , - a ] ) @?= " 0 "
2019-07-15 13:28:52 +03:00
2018-09-04 20:01:26 +03:00
, tests " normaliseMixedAmount " [
2019-11-29 02:29:03 +03:00
test " a missing amount overrides any other amounts " $
2019-11-27 23:46:29 +03:00
normaliseMixedAmount ( Mixed [ usd 1 , missingamt ] ) @?= missingmixedamt
2019-11-29 02:29:03 +03:00
, test " unpriced same-commodity amounts are combined " $
2019-11-27 23:46:29 +03:00
normaliseMixedAmount ( Mixed [ usd 0 , usd 2 ] ) @?= Mixed [ usd 2 ]
2019-11-29 02:29:03 +03:00
, test " amounts with same unit price are combined " $
2019-11-27 23:46:29 +03:00
normaliseMixedAmount ( Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 1 ] ) @?= Mixed [ usd 2 ` at ` eur 1 ]
2019-11-29 02:29:03 +03:00
, test " amounts with different unit prices are not combined " $
2019-11-27 23:46:29 +03:00
normaliseMixedAmount ( Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 2 ] ) @?= Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 2 ]
2019-11-29 02:29:03 +03:00
, test " amounts with total prices are not combined " $
2019-11-27 23:46:29 +03:00
normaliseMixedAmount ( Mixed [ usd 1 @@ eur 1 , usd 1 @@ eur 1 ] ) @?= Mixed [ usd 1 @@ eur 1 , usd 1 @@ eur 1 ]
2018-09-04 20:01:26 +03:00
]
2019-07-15 13:28:52 +03:00
2019-11-29 02:29:03 +03:00
, test " normaliseMixedAmountSquashPricesForDisplay " $ do
2019-11-27 23:46:29 +03:00
normaliseMixedAmountSquashPricesForDisplay ( Mixed [] ) @?= Mixed [ nullamt ]
2020-05-30 04:57:22 +03:00
assertBool " " $ mixedAmountLooksZero $ normaliseMixedAmountSquashPricesForDisplay
2018-09-04 20:01:26 +03:00
( Mixed [ usd 10
, usd 10 @@ eur 7
, usd ( - 10 )
, usd ( - 10 ) @@ eur 7
] )
]
]