2014-10-18 23:09:43 +04:00
{- # LANGUAGE CPP, StandaloneDeriving, RecordWildCards # -}
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
- }
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 ,
hrs ,
at ,
( @@ ) ,
2011-09-02 04:42:41 +04:00
amountWithCommodity ,
2011-08-31 20:54:10 +04:00
-- ** arithmetic
costOfAmount ,
divideAmount ,
-- ** rendering
2012-11-20 01:20:10 +04:00
amountstyle ,
2011-08-31 20:54:10 +04:00
showAmount ,
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 ,
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 ,
2014-07-28 17:32:09 +04:00
normaliseMixedAmountSquashPricesForDisplay ,
normaliseMixedAmount ,
2011-08-31 20:54:10 +04:00
-- ** arithmetic
costOfMixedAmount ,
divideMixedAmount ,
2014-12-26 22:04:23 +03:00
averageMixedAmounts ,
2011-08-31 20:54:10 +04:00
isNegativeMixedAmount ,
isZeroMixedAmount ,
2013-06-02 00:39:00 +04:00
isReallyZeroMixedAmount ,
2011-08-31 20:54:10 +04:00
isReallyZeroMixedAmountCost ,
-- ** rendering
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 ,
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 ,
2011-08-31 20:54:10 +04:00
tests_Hledger_Data_Amount
) where
2011-05-28 08:11:44 +04:00
import Data.Char ( isDigit )
2015-02-27 16:23:07 +03:00
import Data.Decimal ( roundTo )
2014-07-28 17:32:09 +04:00
import Data.Function ( on )
2011-05-28 08:11:44 +04:00
import Data.List
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
2011-05-28 08:11:44 +04:00
import Test.HUnit
import Text.Printf
2012-11-20 01:20:10 +04:00
import qualified Data.Map as M
2010-11-15 02:29:04 +03:00
2010-05-20 03:08:53 +04:00
import Hledger.Data.Types
import Hledger.Data.Commodity
2011-05-28 08:11:44 +04: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
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
2011-08-31 20:54:10 +04:00
-------------------------------------------------------------------------------
-- Amount
2013-12-07 01:51:19 +04:00
instance Show Amount where
show _a @ Amount { .. }
2014-04-02 15:57:33 +04:00
-- debugLevel < 2 = showAmountWithoutPrice a
-- debugLevel < 3 = showAmount a
| debugLevel < 6 =
2013-12-07 01:51:19 +04:00
printf " Amount {acommodity=%s, aquantity=%s, ..} " ( show acommodity ) ( show aquantity )
| otherwise = --showAmountDebug a
printf " Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s} " ( show acommodity ) ( show aquantity ) ( showPriceDebug aprice ) ( show astyle )
2011-08-31 20:54:10 +04:00
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 }
negate a @ Amount { aquantity = q } = a { aquantity = ( - q ) }
( + ) = 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
amount = Amount { acommodity = " " , aquantity = 0 , aprice = NoPrice , astyle = amountstyle }
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 } }
2014-07-28 17:32:09 +04:00
amt ` at ` priceamt = amt { aprice = UnitPrice priceamt }
amt @@ priceamt = amt { aprice = 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
2012-11-20 02:39:08 +04:00
amountWithCommodity c a = a { acommodity = c , aprice = NoPrice }
2010-02-04 19:40:30 +03:00
2011-08-30 17:16:30 +04:00
-- | Convert an amount to the commodity of its assigned price, if any. Notes:
2011-08-31 21:44:31 +04:00
--
2015-06-29 00:13:11 +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
--
2011-04-22 17:44:08 +04:00
-- - price amounts should be positive, though this is not currently enforced
2008-11-22 23:32:58 +03:00
costOfAmount :: Amount -> Amount
2012-11-20 01:20:10 +04:00
costOfAmount a @ Amount { aquantity = q , aprice = price } =
2011-04-22 17:40:55 +04:00
case price of
2012-11-20 02:39:08 +04:00
NoPrice -> a
2012-11-20 03:17:55 +04:00
UnitPrice p @ Amount { aquantity = pq } -> p { aquantity = pq * q }
TotalPrice p @ Amount { aquantity = pq } -> p { aquantity = pq * signum q }
2008-10-15 05:06:05 +04:00
2011-08-31 20:54:10 +04:00
-- | Divide an amount's quantity by a constant.
2014-10-18 23:09:43 +04:00
divideAmount :: Amount -> Quantity -> Amount
2012-11-20 01:20:10 +04:00
divideAmount a @ Amount { aquantity = q } d = a { aquantity = q / d }
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
2011-08-31 20:54:10 +04:00
-- | Does this amount appear to be zero when displayed with its given precision ?
isZeroAmount :: Amount -> Bool
2012-05-27 22:20:18 +04:00
isZeroAmount a -- a==missingamt = False
2012-11-14 21:25:02 +04:00
| otherwise = ( null . filter ( ` elem ` digits ) . showAmountWithoutPriceOrCommodity ) a
2011-08-31 20:54:10 +04:00
-- | Is this amount "really" zero, regardless of the display precision ?
isReallyZeroAmount :: Amount -> Bool
2016-05-19 06:32:58 +03:00
isReallyZeroAmount 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.
2011-08-30 17:16:30 +04:00
setAmountPrecision :: Int -> Amount -> Amount
2012-11-20 01:20:10 +04:00
setAmountPrecision p a @ Amount { astyle = s } = a { astyle = s { asprecision = p } }
-- | Set an amount's display precision, flipped.
withPrecision :: Amount -> Int -> Amount
withPrecision = flip setAmountPrecision
2010-11-13 18:10:06 +03:00
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) "
2013-12-07 01:51:19 +04:00
showAmountDebug Amount { .. } = printf " Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s} " ( show acommodity ) ( show aquantity ) ( showPriceDebug 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
2012-11-20 02:39:08 +04:00
showAmountWithoutPrice a = showAmount a { aprice = NoPrice }
2009-11-25 15:19:02 +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
2012-11-20 02:39:08 +04:00
showAmountWithoutPriceOrCommodity a = showAmount a { acommodity = " " , aprice = NoPrice }
2010-11-15 01:44:37 +03:00
2011-04-22 17:40:55 +04:00
showPrice :: Price -> String
2012-11-20 02:39:08 +04:00
showPrice NoPrice = " "
2012-11-20 03:17:55 +04:00
showPrice ( UnitPrice pa ) = " @ " ++ showAmount pa
showPrice ( TotalPrice pa ) = " @@ " ++ showAmount pa
2011-04-22 17:40:55 +04:00
showPriceDebug :: Price -> String
2012-11-20 02:39:08 +04:00
showPriceDebug NoPrice = " "
2012-11-20 03:17:55 +04:00
showPriceDebug ( UnitPrice pa ) = " @ " ++ showAmountDebug pa
showPriceDebug ( TotalPrice pa ) = " @@ " ++ showAmountDebug pa
2011-04-22 17:40:55 +04:00
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
showAmountHelper :: Bool -> Amount -> String
showAmountHelper _ Amount { acommodity = " AUTO " } = " "
showAmountHelper showzerocommodity a @ ( Amount { acommodity = c , aprice = p , astyle = AmountStyle { .. } } ) =
2012-11-20 01:20:10 +04:00
case ascommodityside of
L -> printf " %s%s%s%s " c' space quantity' price
R -> printf " %s%s%s%s " quantity' space c' price
2011-04-22 17:40:55 +04:00
where
quantity = showamountquantity a
2012-11-14 21:25:02 +04:00
displayingzero = null $ filter ( ` elem ` digits ) $ quantity
2014-07-28 17:32:09 +04:00
( quantity' , c' ) | displayingzero && not showzerocommodity = ( " 0 " , " " )
| otherwise = ( quantity , quoteCommoditySymbolIfNeeded c )
2012-11-20 01:20:10 +04:00
space = if ( not ( null c' ) && ascommodityspaced ) then " " else " " :: String
2012-11-20 02:39:08 +04:00
price = showPrice p
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 } } =
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
2011-01-19 15:32:18 +03:00
-- | Replace a number string's decimal point with the specified character,
2012-11-20 01:20:10 +04:00
-- and add the specified digit group separators. 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
2013-12-07 01:51:19 +04:00
instance Show MixedAmount where
show
2014-04-02 15:56:16 +04:00
| debugLevel < 3 = intercalate " \ \ n " . lines . showMixedAmountWithoutPrice
2013-12-07 01:51:19 +04:00
-- debugLevel < 6 = intercalate "\\n" . lines . showMixedAmount
| otherwise = showMixedAmountDebug
2011-08-31 20:54:10 +04:00
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
( zeros , nonzeros ) = partition isReallyZeroAmount $
map sumSimilarAmountsUsingFirstPrice $
groupBy groupfn $
sortBy sortfn $
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
combinableprices Amount { aprice = NoPrice } Amount { aprice = NoPrice } = True
combinableprices Amount { aprice = UnitPrice p1 } Amount { aprice = UnitPrice p2 } = p1 == p2
combinableprices _ _ = False
tests_normaliseMixedAmount = [
" normaliseMixedAmount " ~: do
-- assertEqual "missing amount is discarded" (Mixed [nullamt]) (normaliseMixedAmount $ Mixed [usd 0, missingamt])
assertEqual " any missing amount means a missing mixed amount " missingmixedamt ( normaliseMixedAmount $ Mixed [ usd 0 , missingamt ] )
assertEqual " unpriced same-commodity amounts are combined " ( Mixed [ usd 2 ] ) ( normaliseMixedAmount $ Mixed [ usd 0 , usd 2 ] )
-- amounts with same unit price are combined
normaliseMixedAmount ( Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 1 ] ) ` is ` Mixed [ usd 2 ` at ` eur 1 ]
-- amounts with different unit prices are not combined
normaliseMixedAmount ( Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 2 ] ) ` is ` Mixed [ usd 1 ` at ` eur 1 , usd 1 ` at ` eur 2 ]
-- amounts with total prices are not combined
normaliseMixedAmount ( Mixed [ usd 1 @@ eur 1 , usd 1 @@ eur 1 ] ) ` is ` Mixed [ usd 1 @@ eur 1 , usd 1 @@ eur 1 ]
2012-05-27 22:14:20 +04:00
]
2014-07-28 17:32:09 +04:00
-- | 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
tests_normaliseMixedAmountSquashPricesForDisplay = [
" normaliseMixedAmountSquashPricesForDisplay " ~: do
normaliseMixedAmountSquashPricesForDisplay ( Mixed [] ) ` is ` Mixed [ nullamt ]
assertBool " " $ isZeroMixedAmount $ normaliseMixedAmountSquashPricesForDisplay
( Mixed [ usd 10
, usd 10 @@ eur 7
, usd ( - 10 )
, usd ( - 10 ) @@ eur 7
] )
]
-- | 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
sumSimilarAmountsUsingFirstPrice as = ( sum as ) { aprice = aprice $ head as }
-- | Sum same-commodity amounts. If there were different prices, set
-- the price to a special marker indicating "various". Only used as a
-- rendering helper.
-- 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'' ]
2011-08-31 20:54:10 +04:00
-- | Convert a mixed amount's component amounts to the commodity of their
-- assigned price, if any.
costOfMixedAmount :: MixedAmount -> MixedAmount
costOfMixedAmount ( Mixed as ) = Mixed $ map costOfAmount as
-- | Divide a mixed amount's quantities by a constant.
2014-10-18 23:09:43 +04:00
divideMixedAmount :: MixedAmount -> Quantity -> MixedAmount
2011-08-31 20:54:10 +04:00
divideMixedAmount ( Mixed as ) d = Mixed $ map ( flip divideAmount d ) as
2014-12-26 22:04:23 +03:00
-- | Calculate the average of some mixed amounts.
averageMixedAmounts :: [ MixedAmount ] -> MixedAmount
averageMixedAmounts [] = 0
averageMixedAmounts as = sum as ` divideMixedAmount ` fromIntegral ( length as )
2011-08-31 20:54:10 +04:00
-- | Is this mixed amount negative, if it can be normalised to a single commodity ?
isNegativeMixedAmount :: MixedAmount -> Maybe Bool
isNegativeMixedAmount m = case as of [ a ] -> Just $ isNegativeAmount a
_ -> Nothing
2014-07-28 17:32:09 +04:00
where as = amounts $ normaliseMixedAmountSquashPricesForDisplay m
2011-08-31 20:54:10 +04:00
2011-04-22 17:50:05 +04:00
-- | Does this mixed amount appear to be zero when displayed with its given precision ?
2008-10-17 07:14:23 +04:00
isZeroMixedAmount :: MixedAmount -> Bool
2014-07-28 17:32:09 +04:00
isZeroMixedAmount = all isZeroAmount . amounts . normaliseMixedAmountSquashPricesForDisplay
2008-10-17 07:14:23 +04:00
2009-05-17 02:54:12 +04:00
-- | Is this mixed amount "really" zero ? See isReallyZeroAmount.
isReallyZeroMixedAmount :: MixedAmount -> Bool
2014-07-28 17:32:09 +04:00
isReallyZeroMixedAmount = all isReallyZeroAmount . amounts . normaliseMixedAmountSquashPricesForDisplay
2009-05-17 02:54:12 +04:00
2010-02-27 21:06:29 +03:00
-- | Is this mixed amount "really" zero, after converting to cost
-- commodities where possible ?
isReallyZeroMixedAmountCost :: MixedAmount -> Bool
isReallyZeroMixedAmountCost = isReallyZeroMixedAmount . costOfMixedAmount
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
-- mixedAmountEquals a b = amounts a' == amounts b' || (isZeroMixedAmount a' && isZeroMixedAmount b')
2014-07-28 17:32:09 +04:00
-- where a' = normaliseMixedAmountSquashPricesForDisplay a
-- b' = normaliseMixedAmountSquashPricesForDisplay b
2009-01-17 21:07:20 +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
2009-11-25 15:19:02 +03:00
-- | Get the string representation of a mixed amount, but without
2009-11-25 15:57:30 +03:00
-- any \@ prices.
2009-11-25 15:19:02 +03:00
showMixedAmountWithoutPrice :: MixedAmount -> String
showMixedAmountWithoutPrice m = concat $ intersperse " \ n " $ map showfixedwidth as
where
2014-07-28 17:32:09 +04:00
( Mixed as ) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
2012-11-20 02:39:08 +04:00
stripPrices ( Mixed as ) = Mixed $ map stripprice as where stripprice a = a { aprice = NoPrice }
2012-05-27 22:14:20 +04:00
width = maximum $ map ( length . showAmount ) as
2009-11-25 15:19:02 +03:00
showfixedwidth = printf ( printf " %%%ds " width ) . showAmountWithoutPrice
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
showMixedAmountOneLineWithoutPrice m = concat $ intersperse " , " $ map showAmountWithoutPrice as
where
2014-07-28 17:32:09 +04:00
( Mixed as ) = normaliseMixedAmountSquashPricesForDisplay $ stripPrices m
2014-07-03 18:45:55 +04:00
stripPrices ( Mixed as ) = Mixed $ map stripprice as where stripprice a = a { aprice = NoPrice }
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
2011-08-31 20:54:10 +04:00
-------------------------------------------------------------------------------
-- misc
2010-03-09 07:03:51 +03:00
2012-05-27 22:14:20 +04:00
tests_Hledger_Data_Amount = TestList $
2014-07-28 17:32:09 +04:00
tests_normaliseMixedAmount
++ tests_normaliseMixedAmountSquashPricesForDisplay
2012-05-27 22:14:20 +04:00
++ [
2010-03-09 07:03:51 +03:00
2011-08-31 20:54:10 +04:00
-- Amount
2011-04-22 17:50:05 +04:00
2011-08-31 04:40:21 +04:00
" costOfAmount " ~: do
2012-11-20 01:20:10 +04:00
costOfAmount ( eur 1 ) ` is ` eur 1
2012-11-20 03:17:55 +04:00
costOfAmount ( eur 2 ) { aprice = UnitPrice $ usd 2 } ` is ` usd 4
costOfAmount ( eur 1 ) { aprice = TotalPrice $ usd 2 } ` is ` usd 2
costOfAmount ( eur ( - 1 ) ) { aprice = TotalPrice $ usd 2 } ` is ` usd ( - 2 )
2010-03-09 07:11:23 +03:00
2011-08-31 04:40:21 +04:00
, " isZeroAmount " ~: do
2012-11-20 01:20:10 +04:00
assertBool " " $ isZeroAmount $ amount
assertBool " " $ isZeroAmount $ usd 0
2011-08-31 04:40:21 +04:00
, " negating amounts " ~: do
2012-11-20 01:20:10 +04:00
let a = usd 1
negate a ` is ` a { aquantity = ( - 1 ) }
2012-11-20 03:17:55 +04:00
let b = ( usd 1 ) { aprice = UnitPrice $ eur 2 }
2012-11-20 01:20:10 +04:00
negate b ` is ` b { aquantity = ( - 1 ) }
2010-03-09 07:03:51 +03:00
2012-11-12 20:31:43 +04:00
, " adding amounts without prices " ~: do
2012-11-20 01:20:10 +04:00
let a1 = usd 1.23
let a2 = usd ( - 1.23 )
let a3 = usd ( - 1.23 )
( a1 + a2 ) ` is ` usd 0
( a1 + a3 ) ` is ` usd 0
( a2 + a3 ) ` is ` usd ( - 2.46 )
( a3 + a3 ) ` is ` usd ( - 2.46 )
sum [ a1 , a2 , a3 , - a3 ] ` is ` usd 0
2011-08-31 04:40:21 +04:00
-- highest precision is preserved
2012-11-20 03:24:04 +04:00
let ap1 = usd 1 ` withPrecision ` 1
ap3 = usd 1 ` withPrecision ` 3
2012-11-20 01:20:10 +04:00
( asprecision $ astyle $ sum [ ap1 , ap3 ] ) ` is ` 3
( asprecision $ astyle $ sum [ ap3 , ap1 ] ) ` is ` 3
2011-08-31 04:40:21 +04:00
-- adding different commodities assumes conversion rate 1
2012-11-20 01:20:10 +04:00
assertBool " " $ isZeroAmount ( a1 - eur 1.23 )
2010-03-09 07:03:51 +03:00
2011-08-31 04:40:21 +04:00
, " showAmount " ~: do
2012-11-20 01:20:10 +04:00
showAmount ( usd 0 + gbp 0 ) ` is ` " 0 "
2011-08-31 04:40:21 +04:00
2011-08-31 20:54:10 +04:00
-- MixedAmount
2010-03-09 07:03:51 +03:00
2015-09-03 02:38:45 +03:00
, " adding mixed amounts to zero, the commodity and amount style are preserved " ~: do
2014-07-28 17:32:09 +04:00
( sum $ map ( Mixed . ( : [] ) )
2012-11-20 01:20:10 +04:00
[ usd 1.25
2015-09-03 02:38:45 +03:00
, usd ( - 1 ) ` withPrecision ` 3
2012-11-20 01:20:10 +04:00
, usd ( - 0.25 )
] )
2015-09-03 02:38:45 +03:00
` is ` Mixed [ usd 0 ` withPrecision ` 3 ]
2014-09-11 00:07:53 +04:00
2012-11-12 20:31:43 +04:00
, " adding mixed amounts with total prices " ~: do
2014-07-28 17:32:09 +04:00
( sum $ map ( Mixed . ( : [] ) )
2012-11-20 01:20:10 +04:00
[ usd 1 @@ eur 1
, usd ( - 2 ) @@ eur 1
2012-11-12 20:31:43 +04:00
] )
2012-11-20 01:20:10 +04:00
` is ` ( Mixed [ usd 1 @@ eur 1
, usd ( - 2 ) @@ eur 1
2012-11-12 20:31:43 +04:00
] )
2011-08-31 04:40:21 +04:00
, " showMixedAmount " ~: do
2012-11-20 01:20:10 +04:00
showMixedAmount ( Mixed [ usd 1 ] ) ` is ` " $1.00 "
showMixedAmount ( Mixed [ usd 1 ` at ` eur 2 ] ) ` is ` " $1.00 @ €2.00 "
showMixedAmount ( Mixed [ usd 0 ] ) ` is ` " 0 "
2011-08-31 04:40:21 +04:00
showMixedAmount ( Mixed [] ) ` is ` " 0 "
2012-05-27 22:14:20 +04:00
showMixedAmount missingmixedamt ` is ` " "
2010-03-09 07:03:51 +03:00
2011-08-31 20:54:10 +04:00
, " showMixedAmountWithoutPrice " ~: do
2012-11-20 01:20:10 +04:00
let a = usd 1 ` at ` eur 2
2011-08-31 20:54:10 +04:00
showMixedAmountWithoutPrice ( Mixed [ a ] ) ` is ` " $1.00 "
showMixedAmountWithoutPrice ( Mixed [ a , ( - a ) ] ) ` is ` " 0 "
2011-04-22 17:40:55 +04:00
2010-03-09 07:03:51 +03:00
]