Safe Haskell | None |
---|---|
Language | Haskell2010 |
Import this module qualified as follows:
import qualified Money
Note: This module exports support for many well-known currencies
out-of-the-box, but you are not limited to the currencies mentioned here. You
can simply create a new Scale
instance, and voilà. If you want to add a
new currency to the out-of-the-box offer, please request so in
https://github.com/k0001/safe-money/issues and the authors will see to it.
This module offers plenty of documentation, but for a deep explanation of how all of the pieces fit together, please read https://ren.zone/articles/safe-money. Notice, however, that this library has changed a bit since that article was written. You can always see the change log to understand what has changed.
Also, keep in mind that useful instances for the many types defined by
safe-money
can be found in these other libraries:
- safe-money-aeson:
FromJSON
andToJSON
instances (from the aeson library). - safe-money-cereal:
Serialize
instances (from the cereal library). - safe-money-serialise:
Serialise
instances (from the serialise library). - safe-money-store:
Store
instances (from the store library). - safe-money-xmlbf:
FromXml
andToXml
instances (from the xmlbf library).
Synopsis
- data Dense (currency :: Symbol)
- denseCurrency :: KnownSymbol currency => Dense currency -> Text
- dense :: Rational -> Maybe (Dense currency)
- dense' :: Rational -> Dense currency
- denseFromDiscrete :: GoodScale scale => Discrete' currency scale -> Dense currency
- denseFromDecimal :: Maybe Char -> Char -> Rational -> Text -> Maybe (Dense currency)
- denseToDecimal :: Approximation -> Bool -> Maybe Char -> Char -> Word8 -> Rational -> Dense currency -> Maybe Text
- type Discrete (currency :: Symbol) (unit :: Symbol) = Discrete' currency (Scale currency unit)
- data Discrete' (currency :: Symbol) (scale :: (Nat, Nat))
- discrete :: GoodScale scale => Integer -> Discrete' currency scale
- discreteCurrency :: (KnownSymbol currency, GoodScale scale) => Discrete' currency scale -> Text
- discreteFromDense :: forall currency scale. GoodScale scale => Approximation -> Dense currency -> (Discrete' currency scale, Dense currency)
- discreteFromDecimal :: GoodScale scale => Maybe Char -> Char -> Rational -> Text -> Maybe (Discrete' currency scale)
- discreteToDecimal :: GoodScale scale => Approximation -> Bool -> Maybe Char -> Char -> Word8 -> Rational -> Discrete' currency scale -> Maybe Text
- type family Scale (currency :: Symbol) (unit :: Symbol) :: (Nat, Nat)
- type GoodScale (scale :: (Nat, Nat)) = (CmpNat 0 (Fst scale) ~ LT, CmpNat 0 (Snd scale) ~ LT, KnownNat (Fst scale), KnownNat (Snd scale))
- type family ErrScaleNonCanonical (currency :: Symbol) :: k where ...
- scale :: forall proxy scale. GoodScale scale => proxy scale -> Rational
- data ExchangeRate (src :: Symbol) (dst :: Symbol)
- exchangeRate :: Rational -> Maybe (ExchangeRate src dst)
- exchange :: ExchangeRate src dst -> Dense src -> Dense dst
- exchangeRateRecip :: ExchangeRate a b -> ExchangeRate b a
- exchangeRateFromDecimal :: Maybe Char -> Char -> Text -> Maybe (ExchangeRate src dst)
- exchangeRateToDecimal :: Approximation -> Maybe Char -> Char -> Word8 -> ExchangeRate src dst -> Maybe Text
- exchangeRateToRational :: ExchangeRate src dst -> Rational
- data SomeDense
- toSomeDense :: KnownSymbol currency => Dense currency -> SomeDense
- mkSomeDense :: Text -> Rational -> Maybe SomeDense
- fromSomeDense :: forall currency. KnownSymbol currency => SomeDense -> Maybe (Dense currency)
- withSomeDense :: SomeDense -> (forall currency. KnownSymbol currency => Dense currency -> r) -> r
- someDenseCurrency :: SomeDense -> Text
- someDenseAmount :: SomeDense -> Rational
- data SomeDiscrete
- toSomeDiscrete :: (KnownSymbol currency, GoodScale scale) => Discrete' currency scale -> SomeDiscrete
- mkSomeDiscrete :: Text -> Rational -> Integer -> Maybe SomeDiscrete
- fromSomeDiscrete :: forall currency scale. (KnownSymbol currency, GoodScale scale) => SomeDiscrete -> Maybe (Discrete' currency scale)
- withSomeDiscrete :: forall r. SomeDiscrete -> (forall currency scale. (KnownSymbol currency, GoodScale scale) => Discrete' currency scale -> r) -> r
- someDiscreteCurrency :: SomeDiscrete -> Text
- someDiscreteScale :: SomeDiscrete -> Rational
- someDiscreteAmount :: SomeDiscrete -> Integer
- data SomeExchangeRate
- toSomeExchangeRate :: (KnownSymbol src, KnownSymbol dst) => ExchangeRate src dst -> SomeExchangeRate
- mkSomeExchangeRate :: Text -> Text -> Rational -> Maybe SomeExchangeRate
- fromSomeExchangeRate :: forall src dst. (KnownSymbol src, KnownSymbol dst) => SomeExchangeRate -> Maybe (ExchangeRate src dst)
- withSomeExchangeRate :: SomeExchangeRate -> (forall src dst. (KnownSymbol src, KnownSymbol dst) => ExchangeRate src dst -> r) -> r
- someExchangeRateSrcCurrency :: SomeExchangeRate -> Text
- someExchangeRateDstCurrency :: SomeExchangeRate -> Text
- someExchangeRateRate :: SomeExchangeRate -> Rational
- data Approximation
Dense monetary values
data Dense (currency :: Symbol) Source #
Dense
represents a dense monetary value for currency
(usually a
ISO-4217 currency code, but not necessarily) as a rational number.
While monetary values associated with a particular currency are
discrete (e.g., an exact number of coins and bills), you can still treat
monetary values as dense while operating on them. For example, the half
of USD 3.41
is USD 1.705
, which is not an amount that can't be
represented as a number of USD cents (the smallest unit that can
represent USD amounts). Nevertheless, if you do manage to represent USD
1.709
somehow, and you eventually multiply USD 1.705
by 4
for
example, then you end up with USD 6.82
, which is again a value
representable as USD cents. In other words, Dense
monetary values
allow us to perform precise calculations deferring the conversion to a
Discrete
monetary values as much as posible. Once you are ready to
approximate a Dense
value to a Discrete
value you can use one
discreteFromDense
. Otherwise, using toRational
you can obtain a
precise Rational
representation.
Instances
Eq (Dense currency) Source # | |
ErrFractionalDense => Fractional (Dense currency) Source # | |
Num (Dense currency) Source # | Notice that multiplication of ( How is ( ( That is:
In fact, ( ( |
Defined in Money.Internal (+) :: Dense currency -> Dense currency -> Dense currency # (-) :: Dense currency -> Dense currency -> Dense currency # (*) :: Dense currency -> Dense currency -> Dense currency # negate :: Dense currency -> Dense currency # abs :: Dense currency -> Dense currency # signum :: Dense currency -> Dense currency # fromInteger :: Integer -> Dense currency # | |
Ord (Dense currency) Source # | |
Defined in Money.Internal compare :: Dense currency -> Dense currency -> Ordering # (<) :: Dense currency -> Dense currency -> Bool # (<=) :: Dense currency -> Dense currency -> Bool # (>) :: Dense currency -> Dense currency -> Bool # (>=) :: Dense currency -> Dense currency -> Bool # | |
KnownSymbol currency => Read (Dense currency) Source # | |
Real (Dense currency) Source # | |
Defined in Money.Internal toRational :: Dense currency -> Rational # | |
KnownSymbol currency => Show (Dense currency) Source # | > |
Generic (Dense currency) Source # | |
Arbitrary (Dense currency) Source # | |
KnownSymbol currency => Binary (Dense currency) Source # | Compatible with |
NFData (Dense currency) Source # | |
Defined in Money.Internal | |
Hashable (Dense currency) Source # | |
Defined in Money.Internal | |
VectorSpace (Dense currency) Source # | WARNING a scalar with a zero denominator will cause |
AdditiveGroup (Dense currency) Source # | |
type Rep (Dense currency) Source # | |
Defined in Money.Internal | |
type Scalar (Dense currency) Source # | |
Defined in Money.Internal |
denseCurrency :: KnownSymbol currency => Dense currency -> Text Source #
Dense
currency identifier.
>denseCurrency
(dense'
4 ::Dense
"USD") "USD"
dense :: Rational -> Maybe (Dense currency) Source #
Build a Dense
monetary value from a Rational
value.
For example, if you want to represent USD 12.52316
, then you can use:
dense
(125316%
10000)
Notice that dense
returns Nothing
in case the given Rational'
s
denominator is zero, which although unlikely, it is possible if the
Rational
was unsafely constructed. When dealing with hardcoded or trusted
Rational
values, you can use dense'
instead of dense
which unsafely
constructs a Dense
.
dense' :: Rational -> Dense currency Source #
Unsafely build a Dense
monetary value from a Rational
value. Contrary
to dense
, this function *crashes* if the given Rational
has zero as a
denominator, which is something very unlikely to happen unless the given
Rational
was itself unsafely constructed. Other than that, dense
and
dense'
behave the same.
Prefer to use dense
when dealing with Rational
inputs from untrusted
sources.
denominator
x /= 0 ⇒dense
x ==Just
(dense'
x)
denominator
x == 0 ⇒undefined
==dense'
x
:: Maybe Char | Thousands separator for the integer part, if any (i.e., the |
-> Char | Decimal separator (i.e., the |
-> Rational | Scale used by the rendered decimal. It is important to get this number
correctly, otherwise the resulting In summary, this scale will have a value of |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (Dense currency) |
Parses a decimal representation of a Dense
.
Leading '-'
and '+'
characters are considered.
:: Approximation | Approximation to use if necesary in order to fit the |
-> Bool | Whether to render a leading |
-> Maybe Char | Thousands separator for the integer part, if any (i.e., the If the given separator is a digit, or if it is equal to the decimal
separator, then this functions returns |
-> Char | Decimal separator (i.e., the If the given separator is a digit, or if it is equal to the thousands
separator, then this functions returns |
-> Word8 | Number of decimal numbers to render, if any. |
-> Rational | Scale used to when rendering the decimal number. This is useful if you want to render a “number of cents” rather than a “number of dollars” when rendering a USD amount, for example. Set this to For example, when rendering render You can easily obtain the scale for a particular currency and unit
combination using the Specifying scales other than Be careful when using a scale smaller than |
-> Dense currency | The dense monetary amount to render. |
-> Maybe Text | Returns |
Render a Dense
monetary amount as a decimal number in a potentially lossy
manner.
>denseToDecimal
Round
True
(Just
',') '.' 2 (1%
1) (dense'
(123456%
100) ::Dense
"USD") Just "+1,234.56"
>denseToDecimal
Round
True
(Just
',') '.' 2 (100%
1) (dense'
(123456%
100) ::Dense
"USD") Just "+123,456.00"
This function returns Nothing
if the scale is less than 1
, or if it's not
possible to reliably render the decimal string due to a bad choice of
separators. That is, if the separators are digits or equal among themselves,
this function returns Nothing
.
Discrete monetary values
type Discrete (currency :: Symbol) (unit :: Symbol) = Discrete' currency (Scale currency unit) Source #
Discrete
represents a discrete monetary value for a currency
expresed
as an integer amount of a particular unit
. For example, with currency ~
"USD"
and unit ~ "cent"
you can represent United States Dollars to
their full extent.
currency
is usually a ISO-4217 currency code, but not necessarily.
Construct Discrete
values using discrete
, fromIntegral
, fromInteger
,
discreteFromDense
, discreteFromDecimal
.
For example, if you want to represent GBP 21.05
, where the smallest
represetable unit for a GBP (United Kingdom Pound) is the penny, and 100
pennies equal 1 GBP (i.e.,
), then you can
use:Scale
"GBP" ~ '(100, 1)
discrete
2105 ::Discrete
"GBP" "penny"
Because 2015 / 100 == 20.15
.
data Discrete' (currency :: Symbol) (scale :: (Nat, Nat)) Source #
Discrete'
represents a discrete monetary value for a currency
expresed
as amount of scale
, which is a rational number expressed as (numerator,
denominator)
.
You'll be using Discrete
instead of Discrete'
most of the time, which
mentions the unit name (such as cent or centavo) instead of explicitely
mentioning the unit scale.
Instances
GoodScale scale => Enum (Discrete' currency scale) Source # | |
Defined in Money.Internal succ :: Discrete' currency scale -> Discrete' currency scale # pred :: Discrete' currency scale -> Discrete' currency scale # toEnum :: Int -> Discrete' currency scale # fromEnum :: Discrete' currency scale -> Int # enumFrom :: Discrete' currency scale -> [Discrete' currency scale] # enumFromThen :: Discrete' currency scale -> Discrete' currency scale -> [Discrete' currency scale] # enumFromTo :: Discrete' currency scale -> Discrete' currency scale -> [Discrete' currency scale] # enumFromThenTo :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale -> [Discrete' currency scale] # | |
GoodScale scale => Eq (Discrete' currency scale) Source # | |
(ErrFractionalDiscrete, GoodScale scale) => Fractional (Discrete' currency scale) Source # | |
GoodScale scale => Integral (Discrete' currency scale) Source # | |
Defined in Money.Internal quot :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # rem :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # div :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # mod :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # quotRem :: Discrete' currency scale -> Discrete' currency scale -> (Discrete' currency scale, Discrete' currency scale) # divMod :: Discrete' currency scale -> Discrete' currency scale -> (Discrete' currency scale, Discrete' currency scale) # | |
GoodScale scale => Num (Discrete' currency scale) Source # | Notice that multiplication of ( How is ( ( That is:
In fact, ( ( |
Defined in Money.Internal (+) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # (-) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # (*) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # negate :: Discrete' currency scale -> Discrete' currency scale # abs :: Discrete' currency scale -> Discrete' currency scale # signum :: Discrete' currency scale -> Discrete' currency scale # fromInteger :: Integer -> Discrete' currency scale # | |
GoodScale scale => Ord (Discrete' currency scale) Source # | |
Defined in Money.Internal compare :: Discrete' currency scale -> Discrete' currency scale -> Ordering # (<) :: Discrete' currency scale -> Discrete' currency scale -> Bool # (<=) :: Discrete' currency scale -> Discrete' currency scale -> Bool # (>) :: Discrete' currency scale -> Discrete' currency scale -> Bool # (>=) :: Discrete' currency scale -> Discrete' currency scale -> Bool # max :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # min :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale # | |
(KnownSymbol currency, GoodScale scale) => Read (Discrete' currency scale) Source # | |
GoodScale scale => Real (Discrete' currency scale) Source # | |
Defined in Money.Internal toRational :: Discrete' currency scale -> Rational # | |
(KnownSymbol currency, GoodScale scale) => Show (Discrete' currency scale) Source # | > |
GoodScale scale => Generic (Discrete' currency scale) Source # | |
GoodScale scale => Arbitrary (Discrete' currency scale) Source # | |
(KnownSymbol currency, GoodScale scale) => Binary (Discrete' currency scale) Source # | Compatible with |
GoodScale scale => NFData (Discrete' currency scale) Source # | |
Defined in Money.Internal | |
GoodScale scale => Hashable (Discrete' currency scale) Source # | |
Defined in Money.Internal | |
GoodScale scale => VectorSpace (Discrete' currency scale) Source # | |
GoodScale scale => AdditiveGroup (Discrete' currency scale) Source # | |
Defined in Money.Internal | |
type Rep (Discrete' currency scale) Source # | |
Defined in Money.Internal | |
type Scalar (Discrete' currency scale) Source # | |
Defined in Money.Internal |
discrete :: GoodScale scale => Integer -> Discrete' currency scale Source #
Construct a Discrete
value.
:: (KnownSymbol currency, GoodScale scale) | |
=> Discrete' currency scale | |
-> Text |
Discrete
currency identifier.
>discreteCurrency
(discrete
4 ::Discrete
"USD" "cent") "USD"
:: GoodScale scale | |
=> Approximation | Approximation to use if necesary in order to fit the |
-> Dense currency | |
-> (Discrete' currency scale, Dense currency) |
Approximate a Dense
value x
to the nearest value fully representable a
given scale
.
If the given Dense
doesn't fit entirely in the scale
, then a non-zero
Dense
reminder is returned alongside the Discrete
approximation.
Proof that discreteFromDense
doesn't lose money:
x == casediscreteFromDense
a x of (y, z) ->denseFromDiscrete
y + z
:: GoodScale scale | |
=> Maybe Char | Thousands separator for the integer part, if any (i.e., the |
-> Char | Decimal separator (i.e., the |
-> Rational | Scale used by the rendered decimal. It is important to get this number
correctly, otherwise the resulting In summary, this scale will have a value of |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (Discrete' currency scale) |
Parses a decimal representation of a Discrete
.
Leading '-'
and '+'
characters are considered.
Notice that parsing will fail unless the entire precision of the decimal
number can be represented in the desired scale
.
:: GoodScale scale | |
=> Approximation | Approximation to use if necesary in order to fit the |
-> Bool | Whether to render a leading |
-> Maybe Char | Thousands separator for the integer part, if any (i.e., the If the given separator is a digit, or if it is equal to the decimal
separator, then this functions returns |
-> Char | Decimal separator (i.e., the If the given separator is a digit, or if it is equal to the thousands
separator, then this functions returns |
-> Word8 | Number of decimal numbers to render, if any. |
-> Rational | Scale used to when rendering the decimal number. This is useful if you want to render a “number of cents” rather than a “number of dollars” when rendering a USD amount, for example. Set this to For example, when rendering render You can easily obtain the scale for a particular currency and unit
combination using the Specifying scales other than Be careful when using a scale smaller than |
-> Discrete' currency scale | The monetary amount to render. |
-> Maybe Text | Returns |
Render a Discrete'
monetary amount as a decimal number in a potentially
lossy manner.
This is simply a convenient wrapper around denseToDecimal
:
discreteToDecimal
a b c d e f (dis ::Discrete'
currency scale) ==denseToDecimal
a b c d e f (denseFromDiscrete
dis ::Dense
currency)
In particular, the scale
in
has no influence
over the scale in which the decimal number is rendered. Use the Discrete'
currency scaleRational
parameter to this function for modifying that behavior.
Please refer to denseToDecimal
for further documentation.
This function returns Nothing
if the scale is less than 1
, or if it's not
possible to reliably render the decimal string due to a bad choice of
separators. That is, if the separators are digits or equal among themselves,
this function returns Nothing
.
Currency scales
type family Scale (currency :: Symbol) (unit :: Symbol) :: (Nat, Nat) Source #
is an rational number (expressed as Scale
currency unit'(numerator,
denominator)
) indicating how many pieces of unit
fit in currency
.
currency
is usually a ISO-4217 currency code, but not necessarily.
The Scale
will determine how to convert a Dense
value into a
Discrete
value and vice-versa.
For example, there are 100 USD cents in 1 USD, so the scale for this relationship is:
type instance Scale
"USD" "cent" = '(100, 1)
As another example, there is 1 dollar in USD, so the scale for this relationship is:
type instance Scale
"USD" "dollar" = '(1, 1)
When using Discrete
values to represent money, it will be impossible to
represent an amount of currency
smaller than unit
. So, if you decide to
use Scale "USD" "dollar"
as your scale, you will not be able to
represent values such as USD 3.50 or USD 21.87 becacuse they are not exact
multiples of a dollar.
If there exists a canonical smallest unit
that can fully represent the
currency in all its denominations, then an instance
exists.Scale
currency
currency
type instanceScale
"USD" "USD" =Scale
"USD" "cent"
For some monetary values, such as precious metals, there is no smallest representable unit, since you can repeatedly split the precious metal many times before it stops being a precious metal. Nevertheless, for practical purposes we can make a sane arbitrary choice of smallest unit. For example, the base unit for XAU (Gold) is the troy ounce, which is too big to be considered the smallest unit, but we can arbitrarily choose the milligrain as our smallest unit, which is about as heavy as a single grain of table salt and should be sufficiently precise for all monetary practical purposes. A troy ounce equals 480000 milligrains.
type instance Scale
"XAU" "milligrain" = '(480000, 1)
You can use other units such as milligrams for measuring XAU, for example. However, since the amount of milligrams in a troy ounce (31103.477) is not integral, we need to use rational with a denominator different than 1 to express it.
type instance Scale
"XAU" "milligram" = '(31103477, 1000)
If you try to obtain the Scale
of a currency
without an obvious smallest
representable unit
, like XAU, you will get a compile error.
Instances
type Scale "ADA" "ADA" Source # | Ada |
type Scale "ADA" "ada" Source # | |
type Scale "ADA" "lovelace" Source # | |
type Scale "AED" "AED" Source # | United Arab Emirates dirham |
type Scale "AED" "dirham" Source # | |
type Scale "AED" "fils" Source # | |
type Scale "AFN" "AFN" Source # | Afghan afghani |
type Scale "AFN" "afghani" Source # | |
type Scale "AFN" "pul" Source # | |
type Scale "ALL" "ALL" Source # | Albanian lek |
type Scale "ALL" "lek" Source # | |
type Scale "ALL" "qindarke" Source # | |
type Scale "AMD" "AMD" Source # | Armenian dram |
type Scale "AMD" "dram" Source # | |
type Scale "AMD" "luma" Source # | |
type Scale "ANG" "ANG" Source # | Netherlands Antillean guilder |
type Scale "ANG" "cent" Source # | |
type Scale "ANG" "guilder" Source # | |
type Scale "AOA" "AOA" Source # | Angolan kwanza |
type Scale "AOA" "centimo" Source # | |
type Scale "AOA" "kwanza" Source # | |
type Scale "ARS" "ARS" Source # | Argentine peso |
type Scale "ARS" "centavo" Source # | |
type Scale "ARS" "peso" Source # | |
type Scale "AUD" "AUD" Source # | Australian dollar |
type Scale "AUD" "cent" Source # | |
type Scale "AUD" "dollar" Source # | |
type Scale "AWG" "AWG" Source # | Aruban florin |
type Scale "AWG" "cent" Source # | |
type Scale "AWG" "florin" Source # | |
type Scale "AZN" "AZN" Source # | Azerbaijani manat |
type Scale "AZN" "manat" Source # | |
type Scale "AZN" "qapik" Source # | |
type Scale "BAM" "BAM" Source # | Bosnia and Herzegovina convertible mark |
type Scale "BAM" "fening" Source # | |
type Scale "BAM" "mark" Source # | |
type Scale "BBD" "BBD" Source # | Barbadian dollar |
type Scale "BBD" "cent" Source # | |
type Scale "BBD" "dollar" Source # | |
type Scale "BDT" "BDT" Source # | Bangladeshi taka |
type Scale "BDT" "paisa" Source # | |
type Scale "BDT" "taka" Source # | |
type Scale "BGN" "BGN" Source # | Bulgarian lev |
type Scale "BGN" "lev" Source # | |
type Scale "BGN" "stotinka" Source # | |
type Scale "BHD" "BHD" Source # | Bahraini dinar |
type Scale "BHD" "dinar" Source # | |
type Scale "BHD" "fils" Source # | |
type Scale "BIF" "BIF" Source # | Burundi franc |
type Scale "BIF" "centime" Source # | |
type Scale "BIF" "franc" Source # | |
type Scale "BMD" "BMD" Source # | Bermudian dollar |
type Scale "BMD" "cent" Source # | |
type Scale "BMD" "dollar" Source # | |
type Scale "BND" "BND" Source # | Brunei dollar |
type Scale "BND" "dollar" Source # | |
type Scale "BND" "sen" Source # | |
type Scale "BOB" "BOB" Source # | Bolivian boliviano |
type Scale "BOB" "boliviano" Source # | |
type Scale "BOB" "centavo" Source # | |
type Scale "BOV" "BOV" Source # | Bolivian Mvdol |
type Scale "BRL" "BRL" Source # | Brazilian real |
type Scale "BRL" "centavo" Source # | |
type Scale "BRL" "real" Source # | |
type Scale "BSD" "BSD" Source # | Bahamian dollar |
type Scale "BSD" "cent" Source # | |
type Scale "BSD" "dollar" Source # | |
type Scale "BTC" "BTC" Source # | Bitcoin |
type Scale "BTC" "bitcoin" Source # | |
type Scale "BTC" "millibitcoin" Source # | |
type Scale "BTC" "satoshi" Source # | |
type Scale "BTN" "BTN" Source # | Bhutanese ngultrum |
type Scale "BTN" "chetrum" Source # | |
type Scale "BTN" "ngultrum" Source # | |
type Scale "BWP" "BWP" Source # | Botswana pula |
type Scale "BWP" "pula" Source # | |
type Scale "BWP" "thebe" Source # | |
type Scale "BYN" "BYN" Source # | Belarusian ruble |
type Scale "BYR" "BYR" Source # | Belarusian ruble |
type Scale "BYR" "kapyeyka" Source # | |
type Scale "BYR" "ruble" Source # | |
type Scale "BZD" "BZD" Source # | Belize dollar |
type Scale "BZD" "cent" Source # | |
type Scale "BZD" "dollar" Source # | |
type Scale "CAD" "CAD" Source # | Canadian dollar |
type Scale "CAD" "cent" Source # | |
type Scale "CAD" "dollar" Source # | |
type Scale "CDF" "CDF" Source # | Congolese franc |
type Scale "CDF" "centime" Source # | |
type Scale "CDF" "franc" Source # | |
type Scale "CHE" "CHE" Source # | WIR euro |
type Scale "CHF" "CHF" Source # | Swiss franc |
type Scale "CHF" "franc" Source # | |
type Scale "CHF" "rappen" Source # | |
type Scale "CHW" "CHW" Source # | WIR franc |
type Scale "CLF" "CLF" Source # | Chilean unidad de fomento |
type Scale "CLP" "CLP" Source # | Chilean peso |
type Scale "CLP" "centavo" Source # | |
type Scale "CLP" "peso" Source # | |
type Scale "CNY" "CNY" Source # | Chinese Renminbi |
type Scale "CNY" "fen" Source # | |
type Scale "CNY" "yuan" Source # | |
type Scale "COP" "COP" Source # | Colombian peso |
type Scale "COP" "centavo" Source # | |
type Scale "COP" "peso" Source # | |
type Scale "COU" "COU" Source # | Colombian unidad de valor real |
type Scale "CRC" "CRC" Source # | Costa Rican colon |
type Scale "CRC" "centimo" Source # | |
type Scale "CRC" "colon" Source # | |
type Scale "CUC" "CUC" Source # | Cuban peso convertible |
type Scale "CUC" "centavo" Source # | |
type Scale "CUC" "peso" Source # | |
type Scale "CUP" "CUP" Source # | Cuban peso |
type Scale "CUP" "centavo" Source # | |
type Scale "CUP" "peso" Source # | |
type Scale "CVE" "CVE" Source # | Cape Verdean escudo |
type Scale "CVE" "centavo" Source # | |
type Scale "CVE" "escudo" Source # | |
type Scale "CZK" "CZK" Source # | Czech koruna |
type Scale "CZK" "haler" Source # | |
type Scale "CZK" "koruna" Source # | |
type Scale "DJF" "DJF" Source # | Djiboutian franc |
type Scale "DJF" "centime" Source # | |
type Scale "DJF" "franc" Source # | |
type Scale "DKK" "DKK" Source # | Danish krone |
type Scale "DKK" "krone" Source # | |
type Scale "DKK" "ore" Source # | |
type Scale "DOP" "DOP" Source # | Dominican peso |
type Scale "DOP" "centavo" Source # | |
type Scale "DOP" "peso" Source # | |
type Scale "DZD" "DZD" Source # | Algerian dinar |
type Scale "DZD" "dinar" Source # | |
type Scale "DZD" "santeem" Source # | |
type Scale "EGP" "EGP" Source # | Egyptian pound |
type Scale "EGP" "piastre" Source # | |
type Scale "EGP" "pound" Source # | |
type Scale "ERN" "ERN" Source # | Eritrean nakfa |
type Scale "ERN" "cent" Source # | |
type Scale "ERN" "nafka" Source # | |
type Scale "ETB" "ETB" Source # | Ethiopian birr |
type Scale "ETB" "birr" Source # | |
type Scale "ETB" "santim" Source # | |
type Scale "ETH" "ETH" Source # | Ether |
type Scale "ETH" "babbage" Source # | |
type Scale "ETH" "ether" Source # | |
type Scale "ETH" "finney" Source # | |
type Scale "ETH" "gwei" Source # | |
type Scale "ETH" "kwei" Source # | |
type Scale "ETH" "lovelace" Source # | |
type Scale "ETH" "microether" Source # | |
type Scale "ETH" "milliether" Source # | |
type Scale "ETH" "mwei" Source # | |
type Scale "ETH" "shannon" Source # | |
type Scale "ETH" "szabo" Source # | |
type Scale "ETH" "wei" Source # | |
type Scale "EUR" "EUR" Source # | European euro |
type Scale "EUR" "cent" Source # | |
type Scale "EUR" "euro" Source # | |
type Scale "FJD" "FJD" Source # | Fijian dollar |
type Scale "FKP" "FKP" Source # | Falkland Islands pound |
type Scale "FKP" "penny" Source # | |
type Scale "FKP" "pound" Source # | |
type Scale "GBP" "GBP" Source # | Pound sterling |
type Scale "GBP" "penny" Source # | |
type Scale "GBP" "pound" Source # | |
type Scale "GEL" "GEL" Source # | Georgian lari |
type Scale "GEL" "lari" Source # | |
type Scale "GEL" "tetri" Source # | |
type Scale "GHS" "GHS" Source # | Ghanaian cedi |
type Scale "GHS" "cedi" Source # | |
type Scale "GHS" "pesewa" Source # | |
type Scale "GIP" "GIP" Source # | Gibraltar pound |
type Scale "GIP" "penny" Source # | |
type Scale "GIP" "pound" Source # | |
type Scale "GMD" "GMD" Source # | Gambian dalasi |
type Scale "GMD" "butut" Source # | |
type Scale "GMD" "dalasi" Source # | |
type Scale "GNF" "GNF" Source # | Guinean franc |
type Scale "GNF" "centime" Source # | |
type Scale "GNF" "franc" Source # | |
type Scale "GTQ" "GTQ" Source # | Guatemalan quetzal |
type Scale "GTQ" "centavo" Source # | |
type Scale "GTQ" "quetzal" Source # | |
type Scale "GYD" "GYD" Source # | Guyanese dollar |
type Scale "GYD" "cent" Source # | |
type Scale "GYD" "dollar" Source # | |
type Scale "HKD" "HKD" Source # | Hong Kong dollar |
type Scale "HKD" "cent" Source # | |
type Scale "HKD" "dollar" Source # | |
type Scale "HNL" "HNL" Source # | Honduran lempira |
type Scale "HNL" "centavo" Source # | |
type Scale "HNL" "lempira" Source # | |
type Scale "HRK" "HRK" Source # | Croatian kuna |
type Scale "HRK" "kuna" Source # | |
type Scale "HRK" "lipa" Source # | |
type Scale "HTG" "HTG" Source # | Haitian gourde |
type Scale "HTG" "centime" Source # | |
type Scale "HTG" "gourde" Source # | |
type Scale "HUF" "HUF" Source # | Hungarian forint |
type Scale "HUF" "filler" Source # | |
type Scale "HUF" "forint" Source # | |
type Scale "IDR" "IDR" Source # | Indonesian rupiah |
type Scale "IDR" "rupiah" Source # | |
type Scale "IDR" "sen" Source # | |
type Scale "ILS" "ILS" Source # | Israeli new shekel |
type Scale "ILS" "agora" Source # | |
type Scale "ILS" "shekel" Source # | |
type Scale "INR" "INR" Source # | Indian rupee |
type Scale "INR" "paisa" Source # | |
type Scale "INR" "rupee" Source # | |
type Scale "IQD" "IQD" Source # | Iraqi dinar |
type Scale "IQD" "dinar" Source # | |
type Scale "IQD" "fils" Source # | |
type Scale "IRR" "IRR" Source # | Iranian rial |
type Scale "IRR" "dinar" Source # | |
type Scale "IRR" "rial" Source # | |
type Scale "ISK" "ISK" Source # | Icelandic króna |
type Scale "ISK" "eyrir" Source # | |
type Scale "ISK" "krona" Source # | |
type Scale "JMD" "JMD" Source # | Jamaican dollar |
type Scale "JMD" "cent" Source # | |
type Scale "JMD" "dollar" Source # | |
type Scale "JOD" "JOD" Source # | Jordanian dinar |
type Scale "JOD" "dinar" Source # | |
type Scale "JOD" "piastre" Source # | |
type Scale "JPY" "JPY" Source # | Japanese yen |
type Scale "JPY" "sen" Source # | |
type Scale "JPY" "yen" Source # | |
type Scale "KES" "KES" Source # | Kenyan shilling |
type Scale "KES" "cent" Source # | |
type Scale "KES" "shilling" Source # | |
type Scale "KGS" "KGS" Source # | Kyrgyzstani som |
type Scale "KGS" "som" Source # | |
type Scale "KGS" "tyiyn" Source # | |
type Scale "KHR" "KHR" Source # | Cambodian riel |
type Scale "KHR" "riel" Source # | |
type Scale "KHR" "sen" Source # | |
type Scale "KMF" "KMF" Source # | Comorian franc |
type Scale "KMF" "centime" Source # | |
type Scale "KMF" "franc" Source # | |
type Scale "KPW" "KPW" Source # | North Korean won |
type Scale "KPW" "chon" Source # | |
type Scale "KPW" "won" Source # | |
type Scale "KRW" "KRW" Source # | South Korean won |
type Scale "KRW" "jeon" Source # | |
type Scale "KRW" "won" Source # | |
type Scale "KWD" "KWD" Source # | Kuwaiti dinar |
type Scale "KWD" "dinar" Source # | |
type Scale "KWD" "fils" Source # | |
type Scale "KYD" "KYD" Source # | Cayman Islands dollar |
type Scale "KYD" "cent" Source # | |
type Scale "KYD" "dollar" Source # | |
type Scale "KZT" "KZT" Source # | Kazakhstani tenge |
type Scale "KZT" "tenge" Source # | |
type Scale "KZT" "tiyin" Source # | |
type Scale "LAK" "LAK" Source # | Lao kip |
type Scale "LAK" "att" Source # | |
type Scale "LAK" "kip" Source # | |
type Scale "LBP" "LBP" Source # | Lebanese pound |
type Scale "LBP" "piastre" Source # | |
type Scale "LBP" "pound" Source # | |
type Scale "LKR" "LKR" Source # | Sri Lankan rupee |
type Scale "LKR" "cent" Source # | |
type Scale "LKR" "rupee" Source # | |
type Scale "LRD" "LRD" Source # | Liberian dollar |
type Scale "LRD" "cent" Source # | |
type Scale "LRD" "dollar" Source # | |
type Scale "LSL" "LSL" Source # | Lesotho loti |
type Scale "LSL" "loti" Source # | |
type Scale "LSL" "sente" Source # | |
type Scale "LTC" "LTC" Source # | Litecoin |
type Scale "LTC" "lite" Source # | |
type Scale "LTC" "litecoin" Source # | |
type Scale "LTC" "photon" Source # | |
type Scale "LYD" "LYD" Source # | Libyan dinar |
type Scale "LYD" "dinar" Source # | |
type Scale "LYD" "dirham" Source # | |
type Scale "MAD" "MAD" Source # | Moroccan dirham |
type Scale "MAD" "centime" Source # | |
type Scale "MAD" "dirham" Source # | |
type Scale "MDL" "MDL" Source # | Moldovan leu |
type Scale "MDL" "ban" Source # | |
type Scale "MDL" "leu" Source # | |
type Scale "MGA" "MGA" Source # | Malagasy ariary |
type Scale "MGA" "ariary" Source # | |
type Scale "MGA" "iraimbilanja" Source # | |
type Scale "MKD" "MKD" Source # | Macedonian denar |
type Scale "MKD" "denar" Source # | |
type Scale "MKD" "deni" Source # | |
type Scale "MMK" "MMK" Source # | Myanmar kyat |
type Scale "MMK" "kyat" Source # | |
type Scale "MMK" "pya" Source # | |
type Scale "MNT" "MNT" Source # | Mongolian tugrik |
type Scale "MNT" "mongo" Source # | |
type Scale "MNT" "tugrik" Source # | |
type Scale "MOP" "MOP" Source # | Macanese pataca |
type Scale "MOP" "avo" Source # | |
type Scale "MOP" "pataca" Source # | |
type Scale "MRO" "MRO" Source # | Mauritanian ouguiya |
type Scale "MRO" "khoums" Source # | |
type Scale "MRO" "ouguiya" Source # | |
type Scale "MUR" "MUR" Source # | Mauritian rupee |
type Scale "MUR" "cent" Source # | |
type Scale "MUR" "rupee" Source # | |
type Scale "MVR" "MVR" Source # | Maldivian rufiyaa |
type Scale "MVR" "laari" Source # | |
type Scale "MVR" "rufiyaa" Source # | |
type Scale "MWK" "MWK" Source # | Malawian kwacha |
type Scale "MWK" "kwacha" Source # | |
type Scale "MWK" "tambala" Source # | |
type Scale "MXN" "MXN" Source # | Mexican peso |
type Scale "MXN" "centavo" Source # | |
type Scale "MXN" "peso" Source # | |
type Scale "MXV" "MXV" Source # | Mexican unidad de inversion |
type Scale "MYR" "MYR" Source # | Malaysian ringgit |
type Scale "MYR" "ringgit" Source # | |
type Scale "MYR" "sen" Source # | |
type Scale "MZN" "MZN" Source # | Mozambican metical |
type Scale "MZN" "centavo" Source # | |
type Scale "MZN" "metical" Source # | |
type Scale "NAD" "NAD" Source # | Namibian dollar |
type Scale "NAD" "cent" Source # | |
type Scale "NAD" "dollar" Source # | |
type Scale "NGN" "NGN" Source # | Nigerian naira |
type Scale "NGN" "kobo" Source # | |
type Scale "NGN" "naira" Source # | |
type Scale "NIO" "NIO" Source # | Nicaraguan cordoba |
type Scale "NIO" "centavo" Source # | |
type Scale "NIO" "cordoba" Source # | |
type Scale "NOK" "NOK" Source # | Norwegian krone |
type Scale "NOK" "krone" Source # | |
type Scale "NOK" "ore" Source # | |
type Scale "NPR" "NPR" Source # | Nepalese rupee |
type Scale "NPR" "paisa" Source # | |
type Scale "NPR" "rupee" Source # | |
type Scale "NZD" "NZD" Source # | New Zealand dollar |
type Scale "NZD" "cent" Source # | |
type Scale "NZD" "dollar" Source # | |
type Scale "OMR" "OMR" Source # | Omani rial |
type Scale "OMR" "baisa" Source # | |
type Scale "OMR" "rial" Source # | |
type Scale "PAB" "PAB" Source # | Panamenian balboa |
type Scale "PAB" "balboa" Source # | |
type Scale "PAB" "centesimo" Source # | |
type Scale "PEN" "PEN" Source # | Peruvian sol |
type Scale "PEN" "centimo" Source # | |
type Scale "PEN" "sol" Source # | |
type Scale "PGK" "PGK" Source # | Papua New Guinean kina |
type Scale "PGK" "kina" Source # | |
type Scale "PGK" "toea" Source # | |
type Scale "PHP" "PHP" Source # | Philippine peso |
type Scale "PHP" "centavo" Source # | |
type Scale "PHP" "peso" Source # | |
type Scale "PKR" "PKR" Source # | Pakistani rupee |
type Scale "PKR" "paisa" Source # | |
type Scale "PKR" "rupee" Source # | |
type Scale "PLN" "PLN" Source # | Polish zloty |
type Scale "PLN" "grosz" Source # | |
type Scale "PLN" "zloty" Source # | |
type Scale "PYG" "PYG" Source # | Paraguayan guarani |
type Scale "PYG" "centimo" Source # | |
type Scale "PYG" "guarani" Source # | |
type Scale "QAR" "QAR" Source # | Qatari riyal |
type Scale "QAR" "dirham" Source # | |
type Scale "QAR" "riyal" Source # | |
type Scale "RON" "RON" Source # | Romanian leu |
type Scale "RON" "ban" Source # | |
type Scale "RON" "leu" Source # | |
type Scale "RSD" "RSD" Source # | Serbian dinar |
type Scale "RSD" "dinar" Source # | |
type Scale "RSD" "para" Source # | |
type Scale "RUB" "RUB" Source # | Russian ruble |
type Scale "RUB" "kopek" Source # | |
type Scale "RUB" "ruble" Source # | |
type Scale "RWF" "RWF" Source # | Rwandan franc |
type Scale "RWF" "centime" Source # | |
type Scale "RWF" "franc" Source # | |
type Scale "SAR" "SAR" Source # | Saudi Arabian riyal |
type Scale "SAR" "halala" Source # | |
type Scale "SAR" "riyal" Source # | |
type Scale "SBD" "SBD" Source # | Solomon Islands dollar |
type Scale "SBD" "cent" Source # | |
type Scale "SBD" "dollar" Source # | |
type Scale "SCR" "SCR" Source # | Seychellois rupee |
type Scale "SCR" "cent" Source # | |
type Scale "SCR" "rupee" Source # | |
type Scale "SDG" "SDG" Source # | Sudanese pound |
type Scale "SDG" "piastre" Source # | |
type Scale "SDG" "pound" Source # | |
type Scale "SEK" "SEK" Source # | Swedish krona |
type Scale "SEK" "krona" Source # | |
type Scale "SEK" "ore" Source # | |
type Scale "SGD" "SGD" Source # | Singapore dollar |
type Scale "SGD" "cent" Source # | |
type Scale "SGD" "dollar" Source # | |
type Scale "SHP" "SHP" Source # | Saint Helena pound |
type Scale "SHP" "penny" Source # | |
type Scale "SHP" "pound" Source # | |
type Scale "SLL" "SLL" Source # | Sierra Leonean leone |
type Scale "SLL" "cent" Source # | |
type Scale "SLL" "leone" Source # | |
type Scale "SOS" "SOS" Source # | Somali shilling |
type Scale "SOS" "cent" Source # | |
type Scale "SOS" "shilling" Source # | |
type Scale "SRD" "SRD" Source # | Surinamese dollar |
type Scale "SRD" "cent" Source # | |
type Scale "SRD" "dollar" Source # | |
type Scale "SSP" "SSP" Source # | South Sudanese pound |
type Scale "SSP" "piastre" Source # | |
type Scale "SSP" "pound" Source # | |
type Scale "STD" "STD" Source # | Sao Tome and Principe dobra |
type Scale "STD" "centimo" Source # | |
type Scale "STD" "dobra" Source # | |
type Scale "SVC" "SVC" Source # | Salvadoran colon |
type Scale "SVC" "centavo" Source # | |
type Scale "SVC" "colon" Source # | |
type Scale "SYP" "SYP" Source # | Syrian pound |
type Scale "SYP" "piastre" Source # | |
type Scale "SYP" "pound" Source # | |
type Scale "SZL" "SZL" Source # | Swazi lilangeni |
type Scale "SZL" "cent" Source # | |
type Scale "SZL" "lilangeni" Source # | |
type Scale "THB" "THB" Source # | Thai baht |
type Scale "THB" "baht" Source # | |
type Scale "THB" "satang" Source # | |
type Scale "TJS" "TJS" Source # | Tajikistani somoni |
type Scale "TJS" "diram" Source # | |
type Scale "TJS" "somoni" Source # | |
type Scale "TMT" "TMT" Source # | Turkmen manat |
type Scale "TMT" "manat" Source # | |
type Scale "TMT" "tennesi" Source # | |
type Scale "TND" "TND" Source # | Tunisian dinar |
type Scale "TND" "dinar" Source # | |
type Scale "TND" "millime" Source # | |
type Scale "TOP" "TOP" Source # | Tongan pa’anga |
type Scale "TOP" "pa'anga" Source # | |
type Scale "TOP" "seniti" Source # | |
type Scale "TRY" "TRY" Source # | Turkish lira |
type Scale "TRY" "kurus" Source # | |
type Scale "TRY" "lira" Source # | |
type Scale "TTD" "TTD" Source # | Tobago Trinidad and Tobago dollar |
type Scale "TTD" "cent" Source # | |
type Scale "TTD" "dollar" Source # | |
type Scale "TWD" "TWD" Source # | New Taiwan dollar |
type Scale "TWD" "cent" Source # | |
type Scale "TWD" "dollar" Source # | |
type Scale "TZS" "TZS" Source # | Tanzanian shilling |
type Scale "TZS" "cent" Source # | |
type Scale "TZS" "shilling" Source # | |
type Scale "UAH" "UAH" Source # | Ukrainian hryvnia |
type Scale "UAH" "hryvnia" Source # | |
type Scale "UAH" "kopiyka" Source # | |
type Scale "UGX" "UGX" Source # | Ugandan shilling |
type Scale "UGX" "cent" Source # | |
type Scale "UGX" "shilling" Source # | |
type Scale "USD" "USD" Source # | United States dollar |
type Scale "USD" "cent" Source # | |
type Scale "USD" "dollar" Source # | |
type Scale "USN" "USN" Source # | United States dollar (next day) |
type Scale "UYI" "UYI" Source # | Uruguayan peso en unidades |
type Scale "UYU" "UYU" Source # | Uruguayan peso |
type Scale "UYU" "centesimo" Source # | |
type Scale "UYU" "peso" Source # | |
type Scale "UZS" "UZS" Source # | Uzbekistani som |
type Scale "UZS" "som" Source # | |
type Scale "UZS" "tiyin" Source # | |
type Scale "VEF" "VEF" Source # | Venezuelan bolivar |
type Scale "VEF" "bolivar" Source # | |
type Scale "VEF" "centimo" Source # | |
type Scale "VND" "VND" Source # | Vietnamese dong |
type Scale "VND" "dong" Source # | |
type Scale "VND" "hao" Source # | |
type Scale "VUV" "VUV" Source # | Vanuatu vatu |
type Scale "VUV" "vatu" Source # | |
type Scale "WST" "WST" Source # | Samoan tālā |
type Scale "WST" "sene" Source # | |
type Scale "WST" "tala" Source # | |
type Scale "XAF" "XAF" Source # | Central African CFA franc |
type Scale "XAF" "centime" Source # | |
type Scale "XAF" "franc" Source # | |
type Scale "XAG" "XAG" Source # | Silver. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type Scale "XAG" "grain" Source # | |
type Scale "XAG" "gram" Source # | |
type Scale "XAG" "kilogram" Source # | |
type Scale "XAG" "micrograin" Source # | |
type Scale "XAG" "microgram" Source # | |
type Scale "XAG" "milligrain" Source # | |
type Scale "XAG" "milligram" Source # | |
type Scale "XAG" "troy-ounce" Source # | |
type Scale "XAU" "XAU" Source # | Gold. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type Scale "XAU" "grain" Source # | |
type Scale "XAU" "gram" Source # | |
type Scale "XAU" "kilogram" Source # | |
type Scale "XAU" "micrograin" Source # | |
type Scale "XAU" "microgram" Source # | |
type Scale "XAU" "milligrain" Source # | |
type Scale "XAU" "milligram" Source # | |
type Scale "XAU" "troy-ounce" Source # | |
type Scale "XBT" "XBT" Source # | Bitcoin |
type Scale "XBT" "bitcoin" Source # | |
type Scale "XBT" "satoshi" Source # | |
type Scale "XCD" "XCD" Source # | East Caribbean dollar |
type Scale "XCD" "cent" Source # | |
type Scale "XCD" "dollar" Source # | |
type Scale "XDR" "XDR" Source # | International Monetary Fund Special Drawing Right |
type Scale "XMR" "XMR" Source # | Monero |
type Scale "XMR" "centinero" Source # | |
type Scale "XMR" "decinero" Source # | |
type Scale "XMR" "micronero" Source # | |
type Scale "XMR" "millinero" Source # | |
type Scale "XMR" "monero" Source # | |
type Scale "XMR" "nanonero" Source # | |
type Scale "XMR" "piconero" Source # | |
type Scale "XOF" "XOF" Source # | West African CFA franc |
type Scale "XOF" "centime" Source # | |
type Scale "XOF" "franc" Source # | |
type Scale "XPD" "XPD" Source # | Palladium. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type Scale "XPD" "grain" Source # | |
type Scale "XPD" "gram" Source # | |
type Scale "XPD" "kilogram" Source # | |
type Scale "XPD" "micrograin" Source # | |
type Scale "XPD" "microgram" Source # | |
type Scale "XPD" "milligrain" Source # | |
type Scale "XPD" "milligram" Source # | |
type Scale "XPD" "troy-ounce" Source # | |
type Scale "XPF" "XPF" Source # | CFP franc |
type Scale "XPF" "centime" Source # | |
type Scale "XPF" "franc" Source # | |
type Scale "XPT" "XPT" Source # | Platinum. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type Scale "XPT" "grain" Source # | |
type Scale "XPT" "gram" Source # | |
type Scale "XPT" "kilogram" Source # | |
type Scale "XPT" "micrograin" Source # | |
type Scale "XPT" "microgram" Source # | |
type Scale "XPT" "milligrain" Source # | |
type Scale "XPT" "milligram" Source # | |
type Scale "XPT" "troy-ounce" Source # | |
type Scale "XRP" "XRP" Source # | Ripple |
type Scale "XRP" "drop" Source # | |
type Scale "XRP" "ripple" Source # | |
type Scale "XSU" "XSU" Source # | Sucre |
type Scale "XUA" "XUA" Source # | African Development Bank unit of account |
type Scale "YER" "YER" Source # | Yemeni rial |
type Scale "YER" "fils" Source # | |
type Scale "YER" "rial" Source # | |
type Scale "ZAR" "ZAR" Source # | South African rand |
type Scale "ZAR" "cent" Source # | |
type Scale "ZAR" "rand" Source # | |
type Scale "ZMW" "ZMW" Source # | Zambian kwacha |
type Scale "ZMW" "kwacha" Source # | |
type Scale "ZMW" "ngwee" Source # | |
type Scale "ZWL" "ZWL" Source # | Zimbawe dollar |
type Scale "ZWL" "cent" Source # | |
type Scale "ZWL" "dollar" Source # | |
type GoodScale (scale :: (Nat, Nat)) = (CmpNat 0 (Fst scale) ~ LT, CmpNat 0 (Snd scale) ~ LT, KnownNat (Fst scale), KnownNat (Snd scale)) Source #
Constraints to a scale (like the one returned by
)
expected to always be satisfied. In particular, the scale is always
guaranteed to be a positive rational number (Scale
currency unitinfinity
and
notANumber
are forbidden by GoodScale
).
type family ErrScaleNonCanonical (currency :: Symbol) :: k where ... Source #
A friendly TypeError
to use for a currency
that doesn't have a
canonical small unit.
Currency exchange
data ExchangeRate (src :: Symbol) (dst :: Symbol) Source #
Exchange rate for converting monetary values of currency src
into
monetary values of currency dst
by multiplying for it.
For example, if in order to convert USD to GBP we have to multiply by 1.2345, then we can represent this situaion using:
exchangeRate
(12345%
10000) ::Maybe
(ExchangeRate
"USD" "GBP")
Instances
exchangeRate :: Rational -> Maybe (ExchangeRate src dst) Source #
Safely construct an ExchangeRate
from a *positive* Rational
number.
exchange :: ExchangeRate src dst -> Dense src -> Dense dst Source #
Apply the ExchangeRate
to the given
monetary value.Dense
src
Identity law:
exchange
(exchangeRateRecip
x) .exchange
x ==id
Use the Identity law for reasoning about going back and forth between src
and dst
in order to manage any leftovers that might not be representable as
a Discrete
monetary value of src
.
exchangeRateRecip :: ExchangeRate a b -> ExchangeRate b a Source #
Reciprocal ExchangeRate
.
This function retuns the reciprocal or multiplicative inverse of the given
ExchangeRate
, leading to the following identity law:
exchangeRateRecip
.exchangeRateRecip
==id
Note: If ExchangeRate
had a Fractional
instance, then exchangeRateRecip
would be the implementation of recip
.
exchangeRateFromDecimal Source #
:: Maybe Char | Thousands separator for the integer part, if any (i.e., the |
-> Char | Decimal separator (i.e., the |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (ExchangeRate src dst) |
Parses a decimal representation of an ExchangeRate
.
exchangeRateToDecimal Source #
:: Approximation | Approximation to use if necesary in order to fit the |
-> Maybe Char | Thousands separator for the integer part, if any (i.e., the |
-> Char | Decimal separator (i.e., the |
-> Word8 | Number of decimal numbers to render, if any. |
-> ExchangeRate src dst | The |
-> Maybe Text | Returns |
Render a ExchangeRate
as a decimal number in a potentially lossy manner.
>exchangeRateToDecimal
Round
True
(Just
',') '.' 2=<<
(exchangeRate
(123456%
100) ::Maybe
(ExchangeRate
"USD" "EUR")) Just "1,234.56"
This function returns Nothing
if it is not possible to reliably render the
decimal string due to a bad choice of separators. That is, if the separators
are digits or equal among themselves, this function returns Nothing
.
exchangeRateToRational :: ExchangeRate src dst -> Rational Source #
Obtain a Rational
representation of the ExchangeRate
.
This Rational
is guaranteed to be a positive number.
Serializable representations
A monomorphic representation of Dense
that is easier to serialize and
deserialize than Dense
in case you don't know the type indexes involved.
If you are trying to construct a value of this type from some raw input, then
you will need to use the mkSomeDense
function.
In order to be able to effectively serialize a SomeDense
value, you
need to serialize the following three values (which are the eventual
arguments to mkSomeDense
):
Instances
Eq SomeDense Source # | |
Ord SomeDense Source # | WARNING This instance does not compare monetary amounts, it just helps
you sort |
Defined in Money.Internal | |
Show SomeDense Source # | |
Generic SomeDense Source # | |
Arbitrary SomeDense Source # | |
Binary SomeDense Source # | Compatible with |
NFData SomeDense Source # | |
Defined in Money.Internal | |
Hashable SomeDense Source # | |
Defined in Money.Internal | |
type Rep SomeDense Source # | |
Defined in Money.Internal type Rep SomeDense = D1 (MetaData "SomeDense" "Money.Internal" "safe-money-0.7.1-1BcrJESs2d66OOiE9qkUxB" False) (C1 (MetaCons "SomeDense" PrefixI True) (S1 (MetaSel (Just "_someDenseCurrency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: S1 (MetaSel (Just "_someDenseAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Rational))) |
toSomeDense :: KnownSymbol currency => Dense currency -> SomeDense Source #
:: Text | Currency. ( |
-> Rational | Scale. ( |
-> Maybe SomeDense |
:: KnownSymbol currency | |
=> SomeDense | |
-> Maybe (Dense currency) |
:: SomeDense | |
-> (forall currency. KnownSymbol currency => Dense currency -> r) | |
-> r |
Convert a SomeDense
to a Dense
without knowing the target currency
.
Notice that currency
here can't leave its intended scope unless you can
prove equality with some other type at the outer scope, but in that case you
would be better off using fromSomeDense
directly.
someDenseCurrency :: SomeDense -> Text Source #
Currency name.
someDenseAmount :: SomeDense -> Rational Source #
Currency unit amount.
data SomeDiscrete Source #
A monomorphic representation of Discrete
that is easier to serialize and
deserialize than Discrete
in case you don't know the type indexes involved.
If you are trying to construct a value of this type from some raw input, then
you will need to use the mkSomeDiscrete
function.
In order to be able to effectively serialize a SomeDiscrete
value, you need
to serialize the following four values (which are the eventual arguments to
mkSomeDiscrete
):
Instances
:: (KnownSymbol currency, GoodScale scale) | |
=> Discrete' currency scale | |
-> SomeDiscrete |
Convert a Discrete
to a SomeDiscrete
for ease of serialization.
:: Text | Currency name. ( |
-> Rational | Scale. Positive, non-zero. ( |
-> Integer | Amount of unit. ( |
-> Maybe SomeDiscrete |
Internal. Build a SomeDiscrete
from raw values.
This function is intended for deserialization purposes. You need to convert
this SomeDiscrete
value to a Discrete
vallue in order to do any arithmetic
operation on the monetary value.
:: (KnownSymbol currency, GoodScale scale) | |
=> SomeDiscrete | |
-> Maybe (Discrete' currency scale) |
Attempt to convert a SomeDiscrete
to a Discrete
, provided you know the
target currency
and unit
.
:: SomeDiscrete | |
-> (forall currency scale. (KnownSymbol currency, GoodScale scale) => Discrete' currency scale -> r) | |
-> r |
Convert a SomeDiscrete
to a Discrete
without knowing the target
currency
and unit
.
Notice that currency
and unit
here can't leave its intended scope unless
you can prove equality with some other type at the outer scope, but in that
case you would be better off using fromSomeDiscrete
directly.
Notice that you may need to add an explicit type to the result of this function in order to keep the compiler happy.
someDiscreteCurrency :: SomeDiscrete -> Text Source #
Currency name.
someDiscreteScale :: SomeDiscrete -> Rational Source #
Positive, non-zero.
someDiscreteAmount :: SomeDiscrete -> Integer Source #
Amount of currency unit.
data SomeExchangeRate Source #
A monomorphic representation of ExchangeRate
that is easier to serialize
and deserialize than ExchangeRate
in case you don't know the type indexes
involved.
If you are trying to construct a value of this type from some raw input, then
you will need to use the mkSomeExchangeRate
function.
In order to be able to effectively serialize an SomeExchangeRate
value, you
need to serialize the following four values (which are the eventual arguments
to mkSomeExchangeRate
):
Instances
:: (KnownSymbol src, KnownSymbol dst) | |
=> ExchangeRate src dst | |
-> SomeExchangeRate |
Convert a ExchangeRate
to a SomeDiscrete
for ease of serialization.
:: Text | Source currency name. ( |
-> Text | Destination currency name. ( |
-> Rational | Exchange rate . Positive, non-zero. ( |
-> Maybe SomeExchangeRate |
Internal. Build a SomeExchangeRate
from raw values.
This function is intended for deserialization purposes. You need to convert
this SomeExchangeRate
value to a ExchangeRate
value in order to do any
arithmetic operation with the exchange rate.
:: (KnownSymbol src, KnownSymbol dst) | |
=> SomeExchangeRate | |
-> Maybe (ExchangeRate src dst) |
Attempt to convert a SomeExchangeRate
to a ExchangeRate
, provided you
know the target src
and dst
types.
:: SomeExchangeRate | |
-> (forall src dst. (KnownSymbol src, KnownSymbol dst) => ExchangeRate src dst -> r) | |
-> r |
Convert a SomeExchangeRate
to a ExchangeRate
without knowing the target
currency
and unit
.
Notice that src
and dst
here can't leave its intended scope unless
you can prove equality with some other type at the outer scope, but in that
case you would be better off using fromSomeExchangeRate
directly.
someExchangeRateSrcCurrency :: SomeExchangeRate -> Text Source #
Source currency name.
someExchangeRateDstCurrency :: SomeExchangeRate -> Text Source #
Destination currency name.
someExchangeRateRate :: SomeExchangeRate -> Rational Source #
Exchange rate. Positive, non-zero.
Misc
data Approximation Source #
Method for approximating a fractional number to an integer number.
Round | Approximate |
Floor | Approximate |
Ceiling | Approximate |
Truncate | Approximate |