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 UnitScale
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 :: DecimalConf -> Text -> Maybe (Dense currency)
- denseToDecimal :: DecimalConf -> Approximation -> Dense currency -> Text
- type Discrete (currency :: Symbol) (unit :: Symbol) = Discrete' currency (UnitScale 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 => DecimalConf -> Text -> Maybe (Discrete' currency scale)
- discreteToDecimal :: GoodScale scale => DecimalConf -> Approximation -> Discrete' currency scale -> Text
- data Scale
- scaleFromRational :: Rational -> Maybe Scale
- scaleToRational :: Scale -> Rational
- scale :: forall proxy scale. GoodScale scale => proxy scale -> Scale
- type family UnitScale (currency :: Symbol) (unit :: Symbol) :: (Nat, Nat)
- type family CurrencyScale (currency :: 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 ...
- 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 :: DecimalConf -> Text -> Maybe (ExchangeRate src dst)
- exchangeRateToDecimal :: DecimalConf -> Approximation -> ExchangeRate src dst -> 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
- someDenseToDecimal :: DecimalConf -> Approximation -> SomeDense -> Text
- someDenseCurrency :: SomeDense -> Text
- someDenseAmount :: SomeDense -> Rational
- data SomeDiscrete
- toSomeDiscrete :: (KnownSymbol currency, GoodScale scale) => Discrete' currency scale -> SomeDiscrete
- mkSomeDiscrete :: Text -> Scale -> Integer -> 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
- someDiscreteToDecimal :: DecimalConf -> Approximation -> SomeDiscrete -> Text
- someDiscreteCurrency :: SomeDiscrete -> Text
- someDiscreteScale :: SomeDiscrete -> Scale
- 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
- someExchangeRateToDecimal :: DecimalConf -> Approximation -> SomeExchangeRate -> Text
- someExchangeRateSrcCurrency :: SomeExchangeRate -> Text
- someExchangeRateDstCurrency :: SomeExchangeRate -> Text
- someExchangeRateRate :: SomeExchangeRate -> Rational
- data Approximation
- data DecimalConf = DecimalConf {}
- defaultDecimalConf :: DecimalConf
- data Separators
- mkSeparators :: Char -> Maybe Char -> Maybe Separators
- separatorsComma :: Separators
- separatorsCommaDot :: Separators
- separatorsCommaNarrownbsp :: Separators
- separatorsCommaNbsp :: Separators
- separatorsCommaThinsp :: Separators
- separatorsCommaSpace :: Separators
- separatorsDot :: Separators
- separatorsDotComma :: Separators
- separatorsDotNarrownbsp :: Separators
- separatorsDotThinsp :: Separators
- separatorsDotNbsp :: Separators
- separatorsDotSpace :: Separators
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
:: DecimalConf | Config to use for parsing the decimal number. Notice that a leading |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (Dense currency) |
Parses a decimal representation of a Dense
.
:: DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> Dense currency | The monetary amount to render. |
-> Text |
Render a Dense
monetary amount as a decimal number in a potentially lossy
manner.
>denseToDecimal
defaultDecimalConf
Round
(dense'
(123456%
100) ::Dense
"USD") "1234.56"
Discrete monetary values
type Discrete (currency :: Symbol) (unit :: Symbol) = Discrete' currency (UnitScale 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:UnitScale
"GBP" "penny" ~ '(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 necessary 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 | |
=> DecimalConf | Config to use for parsing the decimal number. Notice that a leading |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (Discrete' currency scale) |
Parses a decimal representation of a Discrete
.
Notice that parsing will fail unless the entire precision of the decimal
number can be represented in the desired scale
.
:: GoodScale scale | |
=> DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> Discrete' currency scale | The monetary amount to render. |
-> Text |
Render a Discrete'
monetary amount as a decimal number in a potentially
lossy manner.
This is simply a convenient wrapper around denseToDecimal
:
discreteToDecimal
ds a (dis ::Discrete'
currency scale) ==denseToDecimal
ds a (denseFromDiscrete
dis ::Dense
currency)
In particular, the scale
in
has no influence
over the scale in which the decimal number is rendered. Change the scale
with Discrete'
currency scaledecimalConf_scale
in order to modify that behavior.
Please refer to denseToDecimal
for further documentation.
Currency scales
This is the term-level representation of the “scale” we represent as
(
elsewhere in the type system (e.g., in Nat
, Nat
)GoodScale
or
UnitScale
).
See UnitScale
for a detailed description.
scaleFromRational :: Rational -> Maybe Scale Source #
Construct a Scale
from a positive, non-zero rational number.
Term-level representation of a currrency scale
.
For example, the Scale
for "USD"
in "cent"
s is 100/1
. We can
obtain a term-level representation for it using any of the following:
>scale
(Proxy
::Proxy
(UnitScale
"USD" "cent"))Scale
(100%
1)
>scale
(Proxy
::CurrencyScale
"USD")Scale
(100%
1)
>scale
(x ::Discrete
"USD" "cent")Scale
(100%
1)
The returned Rational
is statically guaranteed to be a positive number.
type family UnitScale (currency :: Symbol) (unit :: Symbol) :: (Nat, Nat) Source #
is an rational number (expressed as UnitScale
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 resulting (
, which is the type-level representation for
what at the term-level we call Nat
, Nat
)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 UnitScale
"USD" "cent" = '(100, 1)
As another example, there is 1 dollar in USD, so the scale for this relationship is:
type instance UnitScale
"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 UnitScale "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.
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 UnitScale
"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 UnitScale
"XAU" "milligram" = '(31103477, 1000)
If you try to obtain the UnitScale
of a currency
without an obvious smallest
representable unit
, like XAU, you will get a compile error.
Instances
type UnitScale "ADA" "ada" Source # | |
type UnitScale "ADA" "lovelace" Source # | |
type UnitScale "AED" "dirham" Source # | |
type UnitScale "AED" "fils" Source # | |
type UnitScale "AFN" "afghani" Source # | |
type UnitScale "AFN" "pul" Source # | |
type UnitScale "ALL" "lek" Source # | |
type UnitScale "ALL" "qindarke" Source # | |
type UnitScale "AMD" "dram" Source # | |
type UnitScale "AMD" "luma" Source # | |
type UnitScale "ANG" "cent" Source # | |
type UnitScale "ANG" "guilder" Source # | |
type UnitScale "AOA" "centimo" Source # | |
type UnitScale "AOA" "kwanza" Source # | |
type UnitScale "ARS" "centavo" Source # | |
type UnitScale "ARS" "peso" Source # | |
type UnitScale "AUD" "cent" Source # | |
type UnitScale "AUD" "dollar" Source # | |
type UnitScale "AWG" "cent" Source # | |
type UnitScale "AWG" "florin" Source # | |
type UnitScale "AZN" "manat" Source # | |
type UnitScale "AZN" "qapik" Source # | |
type UnitScale "BAM" "fening" Source # | |
type UnitScale "BAM" "mark" Source # | |
type UnitScale "BBD" "cent" Source # | |
type UnitScale "BBD" "dollar" Source # | |
type UnitScale "BDT" "paisa" Source # | |
type UnitScale "BDT" "taka" Source # | |
type UnitScale "BGN" "lev" Source # | |
type UnitScale "BGN" "stotinka" Source # | |
type UnitScale "BHD" "dinar" Source # | |
type UnitScale "BHD" "fils" Source # | |
type UnitScale "BIF" "centime" Source # | |
type UnitScale "BIF" "franc" Source # | |
type UnitScale "BMD" "cent" Source # | |
type UnitScale "BMD" "dollar" Source # | |
type UnitScale "BND" "dollar" Source # | |
type UnitScale "BND" "sen" Source # | |
type UnitScale "BOB" "boliviano" Source # | |
type UnitScale "BOB" "centavo" Source # | |
type UnitScale "BRL" "centavo" Source # | |
type UnitScale "BRL" "real" Source # | |
type UnitScale "BSD" "cent" Source # | |
type UnitScale "BSD" "dollar" Source # | |
type UnitScale "BTC" "bitcoin" Source # | |
type UnitScale "BTC" "millibitcoin" Source # | |
type UnitScale "BTC" "satoshi" Source # | |
type UnitScale "BTN" "chetrum" Source # | |
type UnitScale "BTN" "ngultrum" Source # | |
type UnitScale "BWP" "pula" Source # | |
type UnitScale "BWP" "thebe" Source # | |
type UnitScale "BYN" "kapiejka" Source # | |
type UnitScale "BYN" "ruble" Source # | |
type UnitScale "BYR" "kapiejka" Source # | |
type UnitScale "BYR" "ruble" Source # | |
type UnitScale "BZD" "cent" Source # | |
type UnitScale "BZD" "dollar" Source # | |
type UnitScale "CAD" "cent" Source # | |
type UnitScale "CAD" "dollar" Source # | |
type UnitScale "CDF" "centime" Source # | |
type UnitScale "CDF" "franc" Source # | |
type UnitScale "CHF" "franc" Source # | |
type UnitScale "CHF" "rappen" Source # | |
type UnitScale "CLP" "centavo" Source # | |
type UnitScale "CLP" "peso" Source # | |
type UnitScale "CNY" "fen" Source # | |
type UnitScale "CNY" "yuan" Source # | |
type UnitScale "COP" "centavo" Source # | |
type UnitScale "COP" "peso" Source # | |
type UnitScale "CRC" "centimo" Source # | |
type UnitScale "CRC" "colon" Source # | |
type UnitScale "CUC" "centavo" Source # | |
type UnitScale "CUC" "peso" Source # | |
type UnitScale "CUP" "centavo" Source # | |
type UnitScale "CUP" "peso" Source # | |
type UnitScale "CVE" "centavo" Source # | |
type UnitScale "CVE" "escudo" Source # | |
type UnitScale "CZK" "haler" Source # | |
type UnitScale "CZK" "koruna" Source # | |
type UnitScale "DJF" "centime" Source # | |
type UnitScale "DJF" "franc" Source # | |
type UnitScale "DKK" "krone" Source # | |
type UnitScale "DKK" "ore" Source # | |
type UnitScale "DOP" "centavo" Source # | |
type UnitScale "DOP" "peso" Source # | |
type UnitScale "DZD" "dinar" Source # | |
type UnitScale "DZD" "santeem" Source # | |
type UnitScale "EGP" "piastre" Source # | |
type UnitScale "EGP" "pound" Source # | |
type UnitScale "ERN" "cent" Source # | |
type UnitScale "ERN" "nafka" Source # | |
type UnitScale "ETB" "birr" Source # | |
type UnitScale "ETB" "santim" Source # | |
type UnitScale "ETH" "babbage" Source # | |
type UnitScale "ETH" "ether" Source # | |
type UnitScale "ETH" "finney" Source # | |
type UnitScale "ETH" "gwei" Source # | |
type UnitScale "ETH" "kwei" Source # | |
type UnitScale "ETH" "lovelace" Source # | |
type UnitScale "ETH" "microether" Source # | |
type UnitScale "ETH" "milliether" Source # | |
type UnitScale "ETH" "mwei" Source # | |
type UnitScale "ETH" "shannon" Source # | |
type UnitScale "ETH" "szabo" Source # | |
type UnitScale "ETH" "wei" Source # | |
type UnitScale "EUR" "cent" Source # | |
type UnitScale "EUR" "euro" Source # | |
type UnitScale "FJD" "cent" Source # | |
type UnitScale "FJD" "dollar" Source # | |
type UnitScale "FKP" "penny" Source # | |
type UnitScale "FKP" "pound" Source # | |
type UnitScale "GBP" "penny" Source # | |
type UnitScale "GBP" "pound" Source # | |
type UnitScale "GEL" "lari" Source # | |
type UnitScale "GEL" "tetri" Source # | |
type UnitScale "GHS" "cedi" Source # | |
type UnitScale "GHS" "pesewa" Source # | |
type UnitScale "GIP" "penny" Source # | |
type UnitScale "GIP" "pound" Source # | |
type UnitScale "GMD" "butut" Source # | |
type UnitScale "GMD" "dalasi" Source # | |
type UnitScale "GNF" "centime" Source # | |
type UnitScale "GNF" "franc" Source # | |
type UnitScale "GTQ" "centavo" Source # | |
type UnitScale "GTQ" "quetzal" Source # | |
type UnitScale "GYD" "cent" Source # | |
type UnitScale "GYD" "dollar" Source # | |
type UnitScale "HKD" "cent" Source # | |
type UnitScale "HKD" "dollar" Source # | |
type UnitScale "HNL" "centavo" Source # | |
type UnitScale "HNL" "lempira" Source # | |
type UnitScale "HRK" "kuna" Source # | |
type UnitScale "HRK" "lipa" Source # | |
type UnitScale "HTG" "centime" Source # | |
type UnitScale "HTG" "gourde" Source # | |
type UnitScale "HUF" "filler" Source # | |
type UnitScale "HUF" "forint" Source # | |
type UnitScale "IDR" "rupiah" Source # | |
type UnitScale "IDR" "sen" Source # | |
type UnitScale "ILS" "agora" Source # | |
type UnitScale "ILS" "shekel" Source # | |
type UnitScale "INR" "paisa" Source # | |
type UnitScale "INR" "rupee" Source # | |
type UnitScale "IQD" "dinar" Source # | |
type UnitScale "IQD" "fils" Source # | |
type UnitScale "IRR" "dinar" Source # | |
type UnitScale "IRR" "rial" Source # | |
type UnitScale "ISK" "eyrir" Source # | |
type UnitScale "ISK" "krona" Source # | |
type UnitScale "JMD" "cent" Source # | |
type UnitScale "JMD" "dollar" Source # | |
type UnitScale "JOD" "dinar" Source # | |
type UnitScale "JOD" "piastre" Source # | |
type UnitScale "JPY" "sen" Source # | |
type UnitScale "JPY" "yen" Source # | |
type UnitScale "KES" "cent" Source # | |
type UnitScale "KES" "shilling" Source # | |
type UnitScale "KGS" "som" Source # | |
type UnitScale "KGS" "tyiyn" Source # | |
type UnitScale "KHR" "riel" Source # | |
type UnitScale "KHR" "sen" Source # | |
type UnitScale "KMF" "centime" Source # | |
type UnitScale "KMF" "franc" Source # | |
type UnitScale "KPW" "chon" Source # | |
type UnitScale "KPW" "won" Source # | |
type UnitScale "KRW" "jeon" Source # | |
type UnitScale "KRW" "won" Source # | |
type UnitScale "KWD" "dinar" Source # | |
type UnitScale "KWD" "fils" Source # | |
type UnitScale "KYD" "cent" Source # | |
type UnitScale "KYD" "dollar" Source # | |
type UnitScale "KZT" "tenge" Source # | |
type UnitScale "KZT" "tiyin" Source # | |
type UnitScale "LAK" "att" Source # | |
type UnitScale "LAK" "kip" Source # | |
type UnitScale "LBP" "piastre" Source # | |
type UnitScale "LBP" "pound" Source # | |
type UnitScale "LKR" "cent" Source # | |
type UnitScale "LKR" "rupee" Source # | |
type UnitScale "LRD" "cent" Source # | |
type UnitScale "LRD" "dollar" Source # | |
type UnitScale "LSL" "loti" Source # | |
type UnitScale "LSL" "sente" Source # | |
type UnitScale "LTC" "lite" Source # | |
type UnitScale "LTC" "litecoin" Source # | |
type UnitScale "LTC" "photon" Source # | |
type UnitScale "LYD" "dinar" Source # | |
type UnitScale "LYD" "dirham" Source # | |
type UnitScale "MAD" "centime" Source # | |
type UnitScale "MAD" "dirham" Source # | |
type UnitScale "MDL" "ban" Source # | |
type UnitScale "MDL" "leu" Source # | |
type UnitScale "MGA" "ariary" Source # | |
type UnitScale "MGA" "iraimbilanja" Source # | |
type UnitScale "MKD" "denar" Source # | |
type UnitScale "MKD" "deni" Source # | |
type UnitScale "MMK" "kyat" Source # | |
type UnitScale "MMK" "pya" Source # | |
type UnitScale "MNT" "mongo" Source # | |
type UnitScale "MNT" "tugrik" Source # | |
type UnitScale "MOP" "avo" Source # | |
type UnitScale "MOP" "pataca" Source # | |
type UnitScale "MRO" "khoums" Source # | |
type UnitScale "MRO" "ouguiya" Source # | |
type UnitScale "MUR" "cent" Source # | |
type UnitScale "MUR" "rupee" Source # | |
type UnitScale "MVR" "laari" Source # | |
type UnitScale "MVR" "rufiyaa" Source # | |
type UnitScale "MWK" "kwacha" Source # | |
type UnitScale "MWK" "tambala" Source # | |
type UnitScale "MXN" "centavo" Source # | |
type UnitScale "MXN" "peso" Source # | |
type UnitScale "MYR" "ringgit" Source # | |
type UnitScale "MYR" "sen" Source # | |
type UnitScale "MZN" "centavo" Source # | |
type UnitScale "MZN" "metical" Source # | |
type UnitScale "NAD" "cent" Source # | |
type UnitScale "NAD" "dollar" Source # | |
type UnitScale "NGN" "kobo" Source # | |
type UnitScale "NGN" "naira" Source # | |
type UnitScale "NIO" "centavo" Source # | |
type UnitScale "NIO" "cordoba" Source # | |
type UnitScale "NOK" "krone" Source # | |
type UnitScale "NOK" "ore" Source # | |
type UnitScale "NPR" "paisa" Source # | |
type UnitScale "NPR" "rupee" Source # | |
type UnitScale "NZD" "cent" Source # | |
type UnitScale "NZD" "dollar" Source # | |
type UnitScale "OMR" "baisa" Source # | |
type UnitScale "OMR" "rial" Source # | |
type UnitScale "PAB" "balboa" Source # | |
type UnitScale "PAB" "centesimo" Source # | |
type UnitScale "PEN" "centimo" Source # | |
type UnitScale "PEN" "sol" Source # | |
type UnitScale "PGK" "kina" Source # | |
type UnitScale "PGK" "toea" Source # | |
type UnitScale "PHP" "centavo" Source # | |
type UnitScale "PHP" "peso" Source # | |
type UnitScale "PKR" "paisa" Source # | |
type UnitScale "PKR" "rupee" Source # | |
type UnitScale "PLN" "grosz" Source # | |
type UnitScale "PLN" "zloty" Source # | |
type UnitScale "PYG" "centimo" Source # | |
type UnitScale "PYG" "guarani" Source # | |
type UnitScale "QAR" "dirham" Source # | |
type UnitScale "QAR" "riyal" Source # | |
type UnitScale "RON" "ban" Source # | |
type UnitScale "RON" "leu" Source # | |
type UnitScale "RSD" "dinar" Source # | |
type UnitScale "RSD" "para" Source # | |
type UnitScale "RUB" "kopek" Source # | |
type UnitScale "RUB" "ruble" Source # | |
type UnitScale "RWF" "centime" Source # | |
type UnitScale "RWF" "franc" Source # | |
type UnitScale "SAR" "halala" Source # | |
type UnitScale "SAR" "riyal" Source # | |
type UnitScale "SBD" "cent" Source # | |
type UnitScale "SBD" "dollar" Source # | |
type UnitScale "SCR" "cent" Source # | |
type UnitScale "SCR" "rupee" Source # | |
type UnitScale "SDG" "piastre" Source # | |
type UnitScale "SDG" "pound" Source # | |
type UnitScale "SEK" "krona" Source # | |
type UnitScale "SEK" "ore" Source # | |
type UnitScale "SGD" "cent" Source # | |
type UnitScale "SGD" "dollar" Source # | |
type UnitScale "SHP" "penny" Source # | |
type UnitScale "SHP" "pound" Source # | |
type UnitScale "SLL" "cent" Source # | |
type UnitScale "SLL" "leone" Source # | |
type UnitScale "SOS" "cent" Source # | |
type UnitScale "SOS" "shilling" Source # | |
type UnitScale "SRD" "cent" Source # | |
type UnitScale "SRD" "dollar" Source # | |
type UnitScale "SSP" "piastre" Source # | |
type UnitScale "SSP" "pound" Source # | |
type UnitScale "STD" "centimo" Source # | |
type UnitScale "STD" "dobra" Source # | |
type UnitScale "SVC" "centavo" Source # | |
type UnitScale "SVC" "colon" Source # | |
type UnitScale "SYP" "piastre" Source # | |
type UnitScale "SYP" "pound" Source # | |
type UnitScale "SZL" "cent" Source # | |
type UnitScale "SZL" "lilangeni" Source # | |
type UnitScale "THB" "baht" Source # | |
type UnitScale "THB" "satang" Source # | |
type UnitScale "TJS" "diram" Source # | |
type UnitScale "TJS" "somoni" Source # | |
type UnitScale "TMT" "manat" Source # | |
type UnitScale "TMT" "tennesi" Source # | |
type UnitScale "TND" "dinar" Source # | |
type UnitScale "TND" "millime" Source # | |
type UnitScale "TOP" "pa'anga" Source # | |
type UnitScale "TOP" "seniti" Source # | |
type UnitScale "TRY" "kurus" Source # | |
type UnitScale "TRY" "lira" Source # | |
type UnitScale "TTD" "cent" Source # | |
type UnitScale "TTD" "dollar" Source # | |
type UnitScale "TWD" "cent" Source # | |
type UnitScale "TWD" "dollar" Source # | |
type UnitScale "TZS" "cent" Source # | |
type UnitScale "TZS" "shilling" Source # | |
type UnitScale "UAH" "hryvnia" Source # | |
type UnitScale "UAH" "kopiyka" Source # | |
type UnitScale "UGX" "cent" Source # | |
type UnitScale "UGX" "shilling" Source # | |
type UnitScale "USD" "cent" Source # | |
type UnitScale "USD" "dollar" Source # | |
type UnitScale "USN" "cent" Source # | |
type UnitScale "USN" "dollar" Source # | |
type UnitScale "UYU" "centesimo" Source # | |
type UnitScale "UYU" "peso" Source # | |
type UnitScale "UZS" "som" Source # | |
type UnitScale "UZS" "tiyin" Source # | |
type UnitScale "VEF" "bolivar" Source # | |
type UnitScale "VEF" "centimo" Source # | |
type UnitScale "VES" "bolivar" Source # | |
type UnitScale "VES" "centimo" Source # | |
type UnitScale "VND" "dong" Source # | |
type UnitScale "VND" "hao" Source # | |
type UnitScale "VUV" "vatu" Source # | |
type UnitScale "WST" "sene" Source # | |
type UnitScale "WST" "tala" Source # | |
type UnitScale "XAF" "centime" Source # | |
type UnitScale "XAF" "franc" Source # | |
type UnitScale "XAG" "grain" Source # | |
type UnitScale "XAG" "gram" Source # | |
type UnitScale "XAG" "kilogram" Source # | |
type UnitScale "XAG" "micrograin" Source # | |
type UnitScale "XAG" "microgram" Source # | |
type UnitScale "XAG" "milligrain" Source # | |
type UnitScale "XAG" "milligram" Source # | |
type UnitScale "XAG" "troy-ounce" Source # | |
type UnitScale "XAU" "grain" Source # | |
type UnitScale "XAU" "gram" Source # | |
type UnitScale "XAU" "kilogram" Source # | |
type UnitScale "XAU" "micrograin" Source # | |
type UnitScale "XAU" "microgram" Source # | |
type UnitScale "XAU" "milligrain" Source # | |
type UnitScale "XAU" "milligram" Source # | |
type UnitScale "XAU" "troy-ounce" Source # | |
type UnitScale "XBT" "bitcoin" Source # | |
type UnitScale "XBT" "millibitcoin" Source # | |
type UnitScale "XBT" "satoshi" Source # | |
type UnitScale "XCD" "cent" Source # | |
type UnitScale "XCD" "dollar" Source # | |
type UnitScale "XMR" "centinero" Source # | |
type UnitScale "XMR" "decinero" Source # | |
type UnitScale "XMR" "micronero" Source # | |
type UnitScale "XMR" "millinero" Source # | |
type UnitScale "XMR" "monero" Source # | |
type UnitScale "XMR" "nanonero" Source # | |
type UnitScale "XMR" "piconero" Source # | |
type UnitScale "XOF" "centime" Source # | |
type UnitScale "XOF" "franc" Source # | |
type UnitScale "XPD" "grain" Source # | |
type UnitScale "XPD" "gram" Source # | |
type UnitScale "XPD" "kilogram" Source # | |
type UnitScale "XPD" "micrograin" Source # | |
type UnitScale "XPD" "microgram" Source # | |
type UnitScale "XPD" "milligrain" Source # | |
type UnitScale "XPD" "milligram" Source # | |
type UnitScale "XPD" "troy-ounce" Source # | |
type UnitScale "XPF" "centime" Source # | |
type UnitScale "XPF" "franc" Source # | |
type UnitScale "XPT" "grain" Source # | |
type UnitScale "XPT" "gram" Source # | |
type UnitScale "XPT" "kilogram" Source # | |
type UnitScale "XPT" "micrograin" Source # | |
type UnitScale "XPT" "microgram" Source # | |
type UnitScale "XPT" "milligrain" Source # | |
type UnitScale "XPT" "milligram" Source # | |
type UnitScale "XPT" "troy-ounce" Source # | |
type UnitScale "XRP" "drop" Source # | |
type UnitScale "XRP" "ripple" Source # | |
type UnitScale "YER" "fils" Source # | |
type UnitScale "YER" "rial" Source # | |
type UnitScale "ZAR" "cent" Source # | |
type UnitScale "ZAR" "rand" Source # | |
type UnitScale "ZMW" "kwacha" Source # | |
type UnitScale "ZMW" "ngwee" Source # | |
type UnitScale "ZWL" "cent" Source # | |
type UnitScale "ZWL" "dollar" Source # | |
type family CurrencyScale (currency :: Symbol) :: (Nat, Nat) Source #
If there exists a canonical smallest Scale
that can fully represent the
currency
in all its denominations, then
will
return such CurrencyScale
currencyScale
. For example,
evaluates to
CurrencyScale
"USD"
.UnitScale
"USD" "cent"
type instanceCurrencyScale
"USD" =UnitScale
"USD" "cent"
If the currency
doesn't have a canonical smallest Scale
, then
shall be left undefined or fail to compile with a
CurrencyScale
currencyTypeError
. For example
fails with
CurrencyScale
"XAU"
.ErrScaleNonCanonical
"XAU"
Instances
type CurrencyScale "ADA" Source # | Cardano |
Defined in Money | |
type CurrencyScale "AED" Source # | United Arab Emirates dirham |
Defined in Money | |
type CurrencyScale "AFN" Source # | Afghan afghani |
Defined in Money | |
type CurrencyScale "ALL" Source # | Albanian lek |
Defined in Money | |
type CurrencyScale "AMD" Source # | Armenian dram |
Defined in Money | |
type CurrencyScale "ANG" Source # | Netherlands Antillean guilder |
Defined in Money | |
type CurrencyScale "AOA" Source # | Angolan kwanza |
Defined in Money | |
type CurrencyScale "ARS" Source # | Argentine peso |
Defined in Money | |
type CurrencyScale "AUD" Source # | Australian dollar |
Defined in Money | |
type CurrencyScale "AWG" Source # | Aruban florin |
Defined in Money | |
type CurrencyScale "AZN" Source # | Azerbaijani manat |
Defined in Money | |
type CurrencyScale "BAM" Source # | Bosnia and Herzegovina convertible mark |
Defined in Money | |
type CurrencyScale "BBD" Source # | Barbadian dollar |
Defined in Money | |
type CurrencyScale "BDT" Source # | Bangladeshi taka |
Defined in Money | |
type CurrencyScale "BGN" Source # | Bulgarian lev |
Defined in Money | |
type CurrencyScale "BHD" Source # | Bahraini dinar |
Defined in Money | |
type CurrencyScale "BIF" Source # | Burundi franc |
Defined in Money | |
type CurrencyScale "BMD" Source # | Bermudian dollar |
Defined in Money | |
type CurrencyScale "BND" Source # | Brunei dollar |
Defined in Money | |
type CurrencyScale "BOB" Source # | Bolivian boliviano |
Defined in Money | |
type CurrencyScale "BOV" Source # | Bolivian Mvdol |
Defined in Money | |
type CurrencyScale "BRL" Source # | Brazilian real |
Defined in Money | |
type CurrencyScale "BSD" Source # | Bahamian dollar |
Defined in Money | |
type CurrencyScale "BTC" Source # | Bitcoin |
Defined in Money | |
type CurrencyScale "BTN" Source # | Bhutanese ngultrum |
Defined in Money | |
type CurrencyScale "BWP" Source # | Botswana pula |
Defined in Money | |
type CurrencyScale "BYN" Source # | Belarusian ruble |
Defined in Money | |
type CurrencyScale "BYR" Source # | Belarusian ruble |
Defined in Money | |
type CurrencyScale "BZD" Source # | Belize dollar |
Defined in Money | |
type CurrencyScale "CAD" Source # | Canadian dollar |
Defined in Money | |
type CurrencyScale "CDF" Source # | Congolese franc |
Defined in Money | |
type CurrencyScale "CHE" Source # | WIR euro |
Defined in Money | |
type CurrencyScale "CHF" Source # | Swiss franc |
Defined in Money | |
type CurrencyScale "CHW" Source # | WIR franc |
Defined in Money | |
type CurrencyScale "CLF" Source # | Chilean unidad de fomento |
Defined in Money | |
type CurrencyScale "CLP" Source # | Chilean peso |
Defined in Money | |
type CurrencyScale "CNY" Source # | Chinese Renminbi |
Defined in Money | |
type CurrencyScale "COP" Source # | Colombian peso |
Defined in Money | |
type CurrencyScale "COU" Source # | Colombian unidad de valor real |
Defined in Money | |
type CurrencyScale "CRC" Source # | Costa Rican colon |
Defined in Money | |
type CurrencyScale "CUC" Source # | Cuban peso convertible |
Defined in Money | |
type CurrencyScale "CUP" Source # | Cuban peso |
Defined in Money | |
type CurrencyScale "CVE" Source # | Cape Verdean escudo |
Defined in Money | |
type CurrencyScale "CZK" Source # | Czech koruna |
Defined in Money | |
type CurrencyScale "DJF" Source # | Djiboutian franc |
Defined in Money | |
type CurrencyScale "DKK" Source # | Danish krone |
Defined in Money | |
type CurrencyScale "DOP" Source # | Dominican peso |
Defined in Money | |
type CurrencyScale "DZD" Source # | Algerian dinar |
Defined in Money | |
type CurrencyScale "EGP" Source # | Egyptian pound |
Defined in Money | |
type CurrencyScale "ERN" Source # | Eritrean nakfa |
Defined in Money | |
type CurrencyScale "ETB" Source # | Ethiopian birr |
Defined in Money | |
type CurrencyScale "ETH" Source # | Ether |
Defined in Money | |
type CurrencyScale "EUR" Source # | European euro |
Defined in Money | |
type CurrencyScale "FJD" Source # | Fijian dollar |
Defined in Money | |
type CurrencyScale "FKP" Source # | Falkland Islands pound |
Defined in Money | |
type CurrencyScale "GBP" Source # | Pound sterling |
Defined in Money | |
type CurrencyScale "GEL" Source # | Georgian lari |
Defined in Money | |
type CurrencyScale "GHS" Source # | Ghanaian cedi |
Defined in Money | |
type CurrencyScale "GIP" Source # | Gibraltar pound |
Defined in Money | |
type CurrencyScale "GMD" Source # | Gambian dalasi |
Defined in Money | |
type CurrencyScale "GNF" Source # | Guinean franc |
Defined in Money | |
type CurrencyScale "GTQ" Source # | Guatemalan quetzal |
Defined in Money | |
type CurrencyScale "GYD" Source # | Guyanese dollar |
Defined in Money | |
type CurrencyScale "HKD" Source # | Hong Kong dollar |
Defined in Money | |
type CurrencyScale "HNL" Source # | Honduran lempira |
Defined in Money | |
type CurrencyScale "HRK" Source # | Croatian kuna |
Defined in Money | |
type CurrencyScale "HTG" Source # | Haitian gourde |
Defined in Money | |
type CurrencyScale "HUF" Source # | Hungarian forint |
Defined in Money | |
type CurrencyScale "IDR" Source # | Indonesian rupiah |
Defined in Money | |
type CurrencyScale "ILS" Source # | Israeli new shekel |
Defined in Money | |
type CurrencyScale "INR" Source # | Indian rupee |
Defined in Money | |
type CurrencyScale "IQD" Source # | Iraqi dinar |
Defined in Money | |
type CurrencyScale "IRR" Source # | Iranian rial |
Defined in Money | |
type CurrencyScale "ISK" Source # | Icelandic króna |
Defined in Money | |
type CurrencyScale "JMD" Source # | Jamaican dollar |
Defined in Money | |
type CurrencyScale "JOD" Source # | Jordanian dinar |
Defined in Money | |
type CurrencyScale "JPY" Source # | Japanese yen |
Defined in Money | |
type CurrencyScale "KES" Source # | Kenyan shilling |
Defined in Money | |
type CurrencyScale "KGS" Source # | Kyrgyzstani som |
Defined in Money | |
type CurrencyScale "KHR" Source # | Cambodian riel |
Defined in Money | |
type CurrencyScale "KMF" Source # | Comorian franc |
Defined in Money | |
type CurrencyScale "KPW" Source # | North Korean won |
Defined in Money | |
type CurrencyScale "KRW" Source # | South Korean won |
Defined in Money | |
type CurrencyScale "KWD" Source # | Kuwaiti dinar |
Defined in Money | |
type CurrencyScale "KYD" Source # | Cayman Islands dollar |
Defined in Money | |
type CurrencyScale "KZT" Source # | Kazakhstani tenge |
Defined in Money | |
type CurrencyScale "LAK" Source # | Lao kip |
Defined in Money | |
type CurrencyScale "LBP" Source # | Lebanese pound |
Defined in Money | |
type CurrencyScale "LKR" Source # | Sri Lankan rupee |
Defined in Money | |
type CurrencyScale "LRD" Source # | Liberian dollar |
Defined in Money | |
type CurrencyScale "LSL" Source # | Lesotho loti |
Defined in Money | |
type CurrencyScale "LTC" Source # | Litecoin |
Defined in Money | |
type CurrencyScale "LYD" Source # | Libyan dinar |
Defined in Money | |
type CurrencyScale "MAD" Source # | Moroccan dirham |
Defined in Money | |
type CurrencyScale "MDL" Source # | Moldovan leu |
Defined in Money | |
type CurrencyScale "MGA" Source # | Malagasy ariary |
Defined in Money | |
type CurrencyScale "MKD" Source # | Macedonian denar |
Defined in Money | |
type CurrencyScale "MMK" Source # | Myanmar kyat |
Defined in Money | |
type CurrencyScale "MNT" Source # | Mongolian tugrik |
Defined in Money | |
type CurrencyScale "MOP" Source # | Macanese pataca |
Defined in Money | |
type CurrencyScale "MRO" Source # | Mauritanian ouguiya |
Defined in Money | |
type CurrencyScale "MUR" Source # | Mauritian rupee |
Defined in Money | |
type CurrencyScale "MVR" Source # | Maldivian rufiyaa |
Defined in Money | |
type CurrencyScale "MWK" Source # | Malawian kwacha |
Defined in Money | |
type CurrencyScale "MXN" Source # | Mexican peso |
Defined in Money | |
type CurrencyScale "MXV" Source # | Mexican unidad de inversion |
Defined in Money | |
type CurrencyScale "MYR" Source # | Malaysian ringgit |
Defined in Money | |
type CurrencyScale "MZN" Source # | Mozambican metical |
Defined in Money | |
type CurrencyScale "NAD" Source # | Namibian dollar |
Defined in Money | |
type CurrencyScale "NGN" Source # | Nigerian naira |
Defined in Money | |
type CurrencyScale "NIO" Source # | Nicaraguan cordoba |
Defined in Money | |
type CurrencyScale "NOK" Source # | Norwegian krone |
Defined in Money | |
type CurrencyScale "NPR" Source # | Nepalese rupee |
Defined in Money | |
type CurrencyScale "NZD" Source # | New Zealand dollar |
Defined in Money | |
type CurrencyScale "OMR" Source # | Omani rial |
Defined in Money | |
type CurrencyScale "PAB" Source # | Panamenian balboa |
Defined in Money | |
type CurrencyScale "PEN" Source # | Peruvian sol |
Defined in Money | |
type CurrencyScale "PGK" Source # | Papua New Guinean kina |
Defined in Money | |
type CurrencyScale "PHP" Source # | Philippine peso |
Defined in Money | |
type CurrencyScale "PKR" Source # | Pakistani rupee |
Defined in Money | |
type CurrencyScale "PLN" Source # | Polish zloty |
Defined in Money | |
type CurrencyScale "PYG" Source # | Paraguayan guarani |
Defined in Money | |
type CurrencyScale "QAR" Source # | Qatari riyal |
Defined in Money | |
type CurrencyScale "RON" Source # | Romanian leu |
Defined in Money | |
type CurrencyScale "RSD" Source # | Serbian dinar |
Defined in Money | |
type CurrencyScale "RUB" Source # | Russian ruble |
Defined in Money | |
type CurrencyScale "RWF" Source # | Rwandan franc |
Defined in Money | |
type CurrencyScale "SAR" Source # | Saudi Arabian riyal |
Defined in Money | |
type CurrencyScale "SBD" Source # | Solomon Islands dollar |
Defined in Money | |
type CurrencyScale "SCR" Source # | Seychellois rupee |
Defined in Money | |
type CurrencyScale "SDG" Source # | Sudanese pound |
Defined in Money | |
type CurrencyScale "SEK" Source # | Swedish krona |
Defined in Money | |
type CurrencyScale "SGD" Source # | Singapore dollar |
Defined in Money | |
type CurrencyScale "SHP" Source # | Saint Helena pound |
Defined in Money | |
type CurrencyScale "SLL" Source # | Sierra Leonean leone |
Defined in Money | |
type CurrencyScale "SOS" Source # | Somali shilling |
Defined in Money | |
type CurrencyScale "SRD" Source # | Surinamese dollar |
Defined in Money | |
type CurrencyScale "SSP" Source # | South Sudanese pound |
Defined in Money | |
type CurrencyScale "STD" Source # | Sao Tome and Principe dobra |
Defined in Money | |
type CurrencyScale "SVC" Source # | Salvadoran colon |
Defined in Money | |
type CurrencyScale "SYP" Source # | Syrian pound |
Defined in Money | |
type CurrencyScale "SZL" Source # | Swazi lilangeni |
Defined in Money | |
type CurrencyScale "THB" Source # | Thai baht |
Defined in Money | |
type CurrencyScale "TJS" Source # | Tajikistani somoni |
Defined in Money | |
type CurrencyScale "TMT" Source # | Turkmen manat |
Defined in Money | |
type CurrencyScale "TND" Source # | Tunisian dinar |
Defined in Money | |
type CurrencyScale "TOP" Source # | Tongan pa’anga |
Defined in Money | |
type CurrencyScale "TRY" Source # | Turkish lira |
Defined in Money | |
type CurrencyScale "TTD" Source # | Tobago Trinidad and Tobago dollar |
Defined in Money | |
type CurrencyScale "TWD" Source # | New Taiwan dollar |
Defined in Money | |
type CurrencyScale "TZS" Source # | Tanzanian shilling |
Defined in Money | |
type CurrencyScale "UAH" Source # | Ukrainian hryvnia |
Defined in Money | |
type CurrencyScale "UGX" Source # | Ugandan shilling |
Defined in Money | |
type CurrencyScale "USD" Source # | United States dollar |
Defined in Money | |
type CurrencyScale "USN" Source # | United States dollar (next day) |
Defined in Money | |
type CurrencyScale "UYI" Source # | Uruguayan peso en unidades indexadas |
Defined in Money | |
type CurrencyScale "UYU" Source # | Uruguayan peso |
Defined in Money | |
type CurrencyScale "UYW" Source # | Uruguayan unidad previsional |
Defined in Money | |
type CurrencyScale "UZS" Source # | Uzbekistani som |
Defined in Money | |
type CurrencyScale "VEF" Source # | Venezuelan bolivar fuerte |
Defined in Money | |
type CurrencyScale "VES" Source # | Venezuelan bolivar soberano |
Defined in Money | |
type CurrencyScale "VND" Source # | Vietnamese dong |
Defined in Money | |
type CurrencyScale "VUV" Source # | Vanuatu vatu |
Defined in Money | |
type CurrencyScale "WST" Source # | Samoan tālā |
Defined in Money | |
type CurrencyScale "XAF" Source # | Central African CFA franc |
Defined in Money | |
type CurrencyScale "XAG" Source # | Silver. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type CurrencyScale "XAU" Source # | Gold. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type CurrencyScale "XBT" Source # | Bitcoin |
Defined in Money | |
type CurrencyScale "XCD" Source # | East Caribbean dollar |
Defined in Money | |
type CurrencyScale "XDR" Source # | International Monetary Fund Special Drawing Right |
Defined in Money | |
type CurrencyScale "XMR" Source # | Monero |
Defined in Money | |
type CurrencyScale "XOF" Source # | West African CFA franc |
Defined in Money | |
type CurrencyScale "XPD" Source # | Palladium. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type CurrencyScale "XPF" Source # | CFP franc |
Defined in Money | |
type CurrencyScale "XPT" Source # | Platinum. No canonical smallest unit. Unusable instance. |
Defined in Money | |
type CurrencyScale "XRP" Source # | Ripple |
Defined in Money | |
type CurrencyScale "XSU" Source # | Sucre |
Defined in Money | |
type CurrencyScale "XUA" Source # | African Development Bank unit of account |
Defined in Money | |
type CurrencyScale "YER" Source # | Yemeni rial |
Defined in Money | |
type CurrencyScale "ZAR" Source # | South African rand |
Defined in Money | |
type CurrencyScale "ZMW" Source # | Zambian kwacha |
Defined in Money | |
type CurrencyScale "ZWL" Source # | Zimbawe dollar |
Defined in Money |
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 (UnitScale
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 #
:: DecimalConf | Config to use for parsing the decimal number. Notice that a leading |
-> Text | The raw string containing the decimal representation (e.g.,
|
-> Maybe (ExchangeRate src dst) |
Parses a decimal representation of an ExchangeRate
.
exchangeRateToDecimal Source #
:: DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> ExchangeRate src dst | The |
-> Text |
Render a ExchangeRate
as a decimal number in a potentially lossy manner.
>exchangeRateToDecimal
defaultDecimalConf
Round
<$>
(exchangeRate
(123456%
100) ::Maybe
(ExchangeRate
"USD" "EUR")) Just "1,234.56"
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 across
different currencies, 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.9-3wBZbeQDJZCLCTCC6e1kFP" 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 | Amount. ( |
-> 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.
:: DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> SomeDense | The monetary amount to render. |
-> Text |
Like denseToDecimal
, but takes a SomeDense
as input.
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. ( |
-> Scale | Scale. Positive, non-zero. ( |
-> Integer | Amount of unit. ( |
-> 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.
someDiscreteToDecimal Source #
:: DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> SomeDiscrete | The monetary amount to render. |
-> Text |
Like discreteToDecimal
, but takes a SomeDiscrete
as input.
someDiscreteCurrency :: SomeDiscrete -> Text Source #
Currency name.
someDiscreteScale :: SomeDiscrete -> Scale 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.
someExchangeRateToDecimal Source #
:: DecimalConf | Config to use for rendering the decimal number. |
-> Approximation | Approximation to use if necessary in order to fit the |
-> SomeExchangeRate | The |
-> Text |
Like exchangeRateToDecimal
, but takes a SomeExchangeRate
as input.
someExchangeRateSrcCurrency :: SomeExchangeRate -> Text Source #
Source currency name.
someExchangeRateDstCurrency :: SomeExchangeRate -> Text Source #
Destination currency name.
someExchangeRateRate :: SomeExchangeRate -> Rational Source #
Exchange rate. Positive, non-zero.
Miscellaneous
data Approximation Source #
Method for approximating a fractional number to an integer number.
Round | Approximate |
Floor | Approximate |
Ceiling | Approximate |
Truncate | Approximate |
HalfEven | Approximate |
Instances
Decimal config
data DecimalConf Source #
Config to use when rendering or parsing decimal numbers.
See defaultDecimalConf
.
DecimalConf | |
|
Instances
Eq DecimalConf Source # | |
Defined in Money.Internal (==) :: DecimalConf -> DecimalConf -> Bool # (/=) :: DecimalConf -> DecimalConf -> Bool # | |
Show DecimalConf Source # | |
Defined in Money.Internal showsPrec :: Int -> DecimalConf -> ShowS # show :: DecimalConf -> String # showList :: [DecimalConf] -> ShowS # | |
Arbitrary DecimalConf Source # | |
Defined in Money.Internal arbitrary :: Gen DecimalConf # shrink :: DecimalConf -> [DecimalConf] # |
defaultDecimalConf :: DecimalConf Source #
Default DecimalConf
.
- No leading
'+'
sign - No thousands separator
- Decimal separator is
'.'
2
decimal digits- A scale of
1
That is, something like 1.23
or -1234567.89
.
Separators
data Separators Source #
Decimal and thousands separators used when rendering or parsing a decimal number.
Use mkSeparators
to construct.
Instances
Eq Separators Source # | |
Defined in Money.Internal (==) :: Separators -> Separators -> Bool # (/=) :: Separators -> Separators -> Bool # | |
Show Separators Source # | |
Defined in Money.Internal showsPrec :: Int -> Separators -> ShowS # show :: Separators -> String # showList :: [Separators] -> ShowS # | |
Arbitrary Separators Source # | |
Defined in Money.Internal arbitrary :: Gen Separators # shrink :: Separators -> [Separators] # |
:: Char | Decimal separator (i.e., the |
-> Maybe Char | Thousands separator for the integer part, if any (i.e., the |
-> Maybe Separators |
Construct Separators
to use with in DecimalConf
.
The separators can't be an ASCII digit nor control character, and they must be different from each other.
separatorsComma :: Separators Source #
1234567,89
separatorsCommaDot :: Separators Source #
1.234.567,89
separatorsCommaNarrownbsp :: Separators Source #
1 234 567,89
The whitespace is Unicode's NARROW NO-BREAK SPACE (U+202f, 8239,
'\8239'
).
separatorsCommaNbsp :: Separators Source #
1 234 567,89
The whitespace is Unicode's NO-BREAK SPACE (U+00a0, 160, '\160'
).
separatorsCommaThinsp :: Separators Source #
1 234 567,89
The whitespace is Unicode's THIN SPACE (U+2009, 8201, '\8201'
).
separatorsCommaSpace :: Separators Source #
1 234 567,89
The whitespace is ASCII's SPC (U+0020, 32, '\32'
).
separatorsDot :: Separators Source #
1234567.89
separatorsDotComma :: Separators Source #
1,234,567.89
separatorsDotNarrownbsp :: Separators Source #
1 234 567.89
The whitespace is Unicode's NARROW NO-BREAK SPACE (U+202f, 8239,
'\8239'
).
separatorsDotThinsp :: Separators Source #
1 234 567.89
The whitespace is Unicode's THIN SPACE (U+2009, 8201, '\8201'
).
separatorsDotNbsp :: Separators Source #
1 234 567.89
The whitespace is Unicode's NO-BREAK SPACE (U+00a0, 160, '\160'
).
separatorsDotSpace :: Separators Source #
1 234 567.89
The whitespace is ASCII's SPACE (U+0020, 32, '\32'
).