safe-money-0.8.1: Type-safe and lossless encoding and manipulation of money, fiat currencies, crypto currencies and precious metals.

Safe HaskellNone
LanguageHaskell2010

Money

Contents

Description

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:

Synopsis

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 # 
Instance details

Methods

(==) :: Dense currency -> Dense currency -> Bool #

(/=) :: Dense currency -> Dense currency -> Bool #

ErrFractionalDense => Fractional (Dense currency) Source # 
Instance details

Methods

(/) :: Dense currency -> Dense currency -> Dense currency #

recip :: Dense currency -> Dense currency #

fromRational :: Rational -> Dense currency #

Num (Dense currency) Source #

Notice that multiplication of Dense values doesn't make sense:

(*) :: Dense currency -> Dense currency -> Dense currency

How is * implemented, then? It behaves as the scalar multiplication of a Dense amount by a Rational scalar. That is, you can think of * as having one of the the following types:

(*) :: Rational -> Dense currency -> Dense currency
(*) :: Dense currency -> Rational -> Dense currency@

That is:

dense' (1 % 4) * dense' (1 % 2)  ==  dense' (1 % 8)

In fact, * functions exactly as *^ from the VectorSpace instance.

(*)  ==  (*^)
(*)  ==  flip (*^)
Instance details

Methods

(+) :: 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 # 
Instance details

Methods

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 #

max :: Dense currency -> Dense currency -> Dense currency #

min :: Dense currency -> Dense currency -> Dense currency #

KnownSymbol currency => Read (Dense currency) Source # 
Instance details

Methods

readsPrec :: Int -> ReadS (Dense currency) #

readList :: ReadS [Dense currency] #

readPrec :: ReadPrec (Dense currency) #

readListPrec :: ReadPrec [Dense currency] #

Real (Dense currency) Source # 
Instance details

Methods

toRational :: Dense currency -> Rational #

KnownSymbol currency => Show (Dense currency) Source #
> show (dense' (1 % 3) :: Dense "USD")
"Dense \"USD\" 1%3"
Instance details

Methods

showsPrec :: Int -> Dense currency -> ShowS #

show :: Dense currency -> String #

showList :: [Dense currency] -> ShowS #

Generic (Dense currency) Source # 
Instance details

Associated Types

type Rep (Dense currency) :: * -> * #

Methods

from :: Dense currency -> Rep (Dense currency) x #

to :: Rep (Dense currency) x -> Dense currency #

Arbitrary (Dense currency) Source # 
Instance details

Methods

arbitrary :: Gen (Dense currency) #

shrink :: Dense currency -> [Dense currency] #

KnownSymbol currency => Binary (Dense currency) Source #

Compatible with SomeDense.

Instance details

Methods

put :: Dense currency -> Put #

get :: Get (Dense currency) #

putList :: [Dense currency] -> Put #

NFData (Dense currency) Source # 
Instance details

Methods

rnf :: Dense currency -> () #

Hashable (Dense currency) Source # 
Instance details

Methods

hashWithSalt :: Int -> Dense currency -> Int #

hash :: Dense currency -> Int #

VectorSpace (Dense currency) Source #

WARNING a scalar with a zero denominator will cause *^ to crash.

Instance details

Associated Types

type Scalar (Dense currency) :: * #

Methods

(*^) :: Scalar (Dense currency) -> Dense currency -> Dense currency #

AdditiveGroup (Dense currency) Source # 
Instance details

Methods

zeroV :: Dense currency #

(^+^) :: Dense currency -> Dense currency -> Dense currency #

negateV :: Dense currency -> Dense currency #

(^-^) :: Dense currency -> Dense currency -> Dense currency #

type Rep (Dense currency) Source # 
Instance details
type Rep (Dense currency) = D1 (MetaData "Dense" "Money.Internal" "safe-money-0.8.1-inplace" True) (C1 (MetaCons "Dense" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational)))
type Scalar (Dense currency) Source # 
Instance details
type Scalar (Dense currency) = Rational

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

denseFromDiscrete Source #

Arguments

:: GoodScale scale 
=> Discrete' currency scale 
-> Dense currency 

Convert currency Discrete monetary value into a Dense monetary value.

denseFromDecimal Source #

Arguments

:: DecimalConf

Config to use for parsing the decimal number.

Notice that a leading '-' or '+' will always be correctly interpreted, notwithstanding what the “leading '+'” policy is on the given DecimalConf.

-> Text

The raw string containing the decimal representation (e.g., "-1,234.56789").

-> Maybe (Dense currency) 

Parses a decimal representation of a Dense.

denseToDecimal Source #

Arguments

:: DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the Dense amount in as many decimal numbers as requested.

-> 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., UnitScale "GBP" "penny" ~ '(100, 1)), then you can use:

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 # 
Instance details

Methods

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 # 
Instance details

Methods

(==) :: Discrete' currency scale -> Discrete' currency scale -> Bool #

(/=) :: Discrete' currency scale -> Discrete' currency scale -> Bool #

(ErrFractionalDiscrete, GoodScale scale) => Fractional (Discrete' currency scale) Source # 
Instance details

Methods

(/) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale #

recip :: Discrete' currency scale -> Discrete' currency scale #

fromRational :: Rational -> Discrete' currency scale #

GoodScale scale => Integral (Discrete' currency scale) Source # 
Instance details

Methods

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) #

toInteger :: Discrete' currency scale -> Integer #

GoodScale scale => Num (Discrete' currency scale) Source #

Notice that multiplication of Discrete' values doesn't make sense:

(*) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale

How is * implemented, then? It behaves as the scalar multiplication of a Discrete' amount by an Integer scalar. That is, you can think of * as having one of the the following types:

(*) :: Integer -> Discrete' currency scale -> Discrete' currency scale
(*) :: Discrete' currency scale -> Integer -> Discrete' currency scale@

That is:

discrete 2 * discrete 4  ==  discrete 8

In fact, * functions exactly as *^ from the VectorSpace instance.

(*)  ==  (*^)
(*)  ==  flip (*^)
Instance details

Methods

(+) :: 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 # 
Instance details

Methods

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 # 
Instance details

Methods

readsPrec :: Int -> ReadS (Discrete' currency scale) #

readList :: ReadS [Discrete' currency scale] #

readPrec :: ReadPrec (Discrete' currency scale) #

readListPrec :: ReadPrec [Discrete' currency scale] #

GoodScale scale => Real (Discrete' currency scale) Source # 
Instance details

Methods

toRational :: Discrete' currency scale -> Rational #

(KnownSymbol currency, GoodScale scale) => Show (Discrete' currency scale) Source #
> show (discrete 123 :: Discrete "USD" "cent")
"Discrete \"USD\" 100%1 123"
Instance details

Methods

showsPrec :: Int -> Discrete' currency scale -> ShowS #

show :: Discrete' currency scale -> String #

showList :: [Discrete' currency scale] -> ShowS #

GoodScale scale => Generic (Discrete' currency scale) Source # 
Instance details

Associated Types

type Rep (Discrete' currency scale) :: * -> * #

Methods

from :: Discrete' currency scale -> Rep (Discrete' currency scale) x #

to :: Rep (Discrete' currency scale) x -> Discrete' currency scale #

GoodScale scale => Arbitrary (Discrete' currency scale) Source # 
Instance details

Methods

arbitrary :: Gen (Discrete' currency scale) #

shrink :: Discrete' currency scale -> [Discrete' currency scale] #

(KnownSymbol currency, GoodScale scale) => Binary (Discrete' currency scale) Source #

Compatible with SomeDiscrete.

Instance details

Methods

put :: Discrete' currency scale -> Put #

get :: Get (Discrete' currency scale) #

putList :: [Discrete' currency scale] -> Put #

GoodScale scale => NFData (Discrete' currency scale) Source # 
Instance details

Methods

rnf :: Discrete' currency scale -> () #

GoodScale scale => Hashable (Discrete' currency scale) Source # 
Instance details

Methods

hashWithSalt :: Int -> Discrete' currency scale -> Int #

hash :: Discrete' currency scale -> Int #

GoodScale scale => VectorSpace (Discrete' currency scale) Source # 
Instance details

Associated Types

type Scalar (Discrete' currency scale) :: * #

Methods

(*^) :: Scalar (Discrete' currency scale) -> Discrete' currency scale -> Discrete' currency scale #

GoodScale scale => AdditiveGroup (Discrete' currency scale) Source # 
Instance details

Methods

zeroV :: Discrete' currency scale #

(^+^) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale #

negateV :: Discrete' currency scale -> Discrete' currency scale #

(^-^) :: Discrete' currency scale -> Discrete' currency scale -> Discrete' currency scale #

type Rep (Discrete' currency scale) Source # 
Instance details
type Rep (Discrete' currency scale) = D1 (MetaData "Discrete'" "Money.Internal" "safe-money-0.8.1-inplace" True) (C1 (MetaCons "Discrete" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))
type Scalar (Discrete' currency scale) Source # 
Instance details
type Scalar (Discrete' currency scale) = Integer

discrete :: GoodScale scale => Integer -> Discrete' currency scale Source #

Construct a Discrete value.

discreteCurrency Source #

Arguments

:: (KnownSymbol currency, GoodScale scale) 
=> Discrete' currency scale 
-> Text 

Discrete currency identifier.

> discreteCurrency (discrete 4 :: Discrete "USD" "cent")
"USD"

discreteFromDense Source #

Arguments

:: GoodScale scale 
=> Approximation

Approximation to use if necessary in order to fit the Dense amount in the requested scale.

-> 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 == case discreteFromDense a x of
        (y, z) -> denseFromDiscrete y + z

discreteFromDecimal Source #

Arguments

:: GoodScale scale 
=> DecimalConf

Config to use for parsing the decimal number.

Notice that a leading '-' or '+' will always be correctly interpreted, notwithstanding what the “leading '+'” policy is on the given DecimalConf.

-> Text

The raw string containing the decimal representation (e.g., "-1,234.56789").

-> 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.

discreteToDecimal Source #

Arguments

:: GoodScale scale 
=> DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the Discrete amount in as many decimal numbers as requested.

-> 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 Discrete' currency scale has no influence over the scale in which the decimal number is rendered. Change the scale with decimalConf_scale in order to modify that behavior.

Please refer to denseToDecimal for further documentation.

Currency scales

data Scale Source #

This is the term-level representation of the “scale” we represent as (Nat, Nat) elsewhere in the type system (e.g., in GoodScale or UnitScale).

See UnitScale for a detailed description.

Instances
Eq Scale Source # 
Instance details

Methods

(==) :: Scale -> Scale -> Bool #

(/=) :: Scale -> Scale -> Bool #

Ord Scale Source # 
Instance details

Methods

compare :: Scale -> Scale -> Ordering #

(<) :: Scale -> Scale -> Bool #

(<=) :: Scale -> Scale -> Bool #

(>) :: Scale -> Scale -> Bool #

(>=) :: Scale -> Scale -> Bool #

max :: Scale -> Scale -> Scale #

min :: Scale -> Scale -> Scale #

Show Scale Source # 
Instance details

Methods

showsPrec :: Int -> Scale -> ShowS #

show :: Scale -> String #

showList :: [Scale] -> ShowS #

Generic Scale Source # 
Instance details

Associated Types

type Rep Scale :: * -> * #

Methods

from :: Scale -> Rep Scale x #

to :: Rep Scale x -> Scale #

Arbitrary Scale Source # 
Instance details

Methods

arbitrary :: Gen Scale #

shrink :: Scale -> [Scale] #

Binary Scale Source # 
Instance details

Methods

put :: Scale -> Put #

get :: Get Scale #

putList :: [Scale] -> Put #

NFData Scale Source # 
Instance details

Methods

rnf :: Scale -> () #

Hashable Scale Source # 
Instance details

Methods

hashWithSalt :: Int -> Scale -> Int #

hash :: Scale -> Int #

type Rep Scale Source # 
Instance details
type Rep Scale = D1 (MetaData "Scale" "Money.Internal" "safe-money-0.8.1-inplace" True) (C1 (MetaCons "Scale" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational)))

scaleFromRational :: Rational -> Maybe Scale Source #

Construct a Scale from a positive, non-zero rational number.

scaleToRational :: Scale -> Rational Source #

Obtain the Rational representation of a Scale.

scale Source #

Arguments

:: GoodScale scale 
=> proxy scale 
-> Scale 

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 #

UnitScale currency unit is an rational number (expressed as '(numerator, denominator)) indicating how many pieces of unit fit in currency.

currency is usually a ISO-4217 currency code, but not necessarily.

The resulting (Nat, Nat), which is the type-level representation for what at the term-level we call 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 # 
Instance details
type UnitScale "ADA" "ada" = (,) 1 1
type UnitScale "ADA" "lovelace" Source # 
Instance details
type UnitScale "ADA" "lovelace" = (,) 1000000 1
type UnitScale "AED" "dirham" Source # 
Instance details
type UnitScale "AED" "dirham" = (,) 1 1
type UnitScale "AED" "fils" Source # 
Instance details
type UnitScale "AED" "fils" = (,) 100 1
type UnitScale "AFN" "afghani" Source # 
Instance details
type UnitScale "AFN" "afghani" = (,) 1 1
type UnitScale "AFN" "pul" Source # 
Instance details
type UnitScale "AFN" "pul" = (,) 100 1
type UnitScale "ALL" "lek" Source # 
Instance details
type UnitScale "ALL" "lek" = (,) 1 1
type UnitScale "ALL" "qindarke" Source # 
Instance details
type UnitScale "ALL" "qindarke" = (,) 100 1
type UnitScale "AMD" "dram" Source # 
Instance details
type UnitScale "AMD" "dram" = (,) 1 1
type UnitScale "AMD" "luma" Source # 
Instance details
type UnitScale "AMD" "luma" = (,) 100 1
type UnitScale "ANG" "cent" Source # 
Instance details
type UnitScale "ANG" "cent" = (,) 100 1
type UnitScale "ANG" "guilder" Source # 
Instance details
type UnitScale "ANG" "guilder" = (,) 1 1
type UnitScale "AOA" "centimo" Source # 
Instance details
type UnitScale "AOA" "centimo" = (,) 100 1
type UnitScale "AOA" "kwanza" Source # 
Instance details
type UnitScale "AOA" "kwanza" = (,) 1 1
type UnitScale "ARS" "centavo" Source # 
Instance details
type UnitScale "ARS" "centavo" = (,) 100 1
type UnitScale "ARS" "peso" Source # 
Instance details
type UnitScale "ARS" "peso" = (,) 1 1
type UnitScale "AUD" "cent" Source # 
Instance details
type UnitScale "AUD" "cent" = (,) 100 1
type UnitScale "AUD" "dollar" Source # 
Instance details
type UnitScale "AUD" "dollar" = (,) 1 1
type UnitScale "AWG" "cent" Source # 
Instance details
type UnitScale "AWG" "cent" = (,) 100 1
type UnitScale "AWG" "florin" Source # 
Instance details
type UnitScale "AWG" "florin" = (,) 1 1
type UnitScale "AZN" "manat" Source # 
Instance details
type UnitScale "AZN" "manat" = (,) 1 1
type UnitScale "AZN" "qapik" Source # 
Instance details
type UnitScale "AZN" "qapik" = (,) 100 1
type UnitScale "BAM" "fening" Source # 
Instance details
type UnitScale "BAM" "fening" = (,) 100 1
type UnitScale "BAM" "mark" Source # 
Instance details
type UnitScale "BAM" "mark" = (,) 1 1
type UnitScale "BBD" "cent" Source # 
Instance details
type UnitScale "BBD" "cent" = (,) 100 1
type UnitScale "BBD" "dollar" Source # 
Instance details
type UnitScale "BBD" "dollar" = (,) 1 1
type UnitScale "BDT" "paisa" Source # 
Instance details
type UnitScale "BDT" "paisa" = (,) 100 1
type UnitScale "BDT" "taka" Source # 
Instance details
type UnitScale "BDT" "taka" = (,) 1 1
type UnitScale "BGN" "lev" Source # 
Instance details
type UnitScale "BGN" "lev" = (,) 1 1
type UnitScale "BGN" "stotinka" Source # 
Instance details
type UnitScale "BGN" "stotinka" = (,) 100 1
type UnitScale "BHD" "dinar" Source # 
Instance details
type UnitScale "BHD" "dinar" = (,) 1 1
type UnitScale "BHD" "fils" Source # 
Instance details
type UnitScale "BHD" "fils" = (,) 1000 1
type UnitScale "BIF" "centime" Source # 
Instance details
type UnitScale "BIF" "centime" = (,) 100 1
type UnitScale "BIF" "franc" Source # 
Instance details
type UnitScale "BIF" "franc" = (,) 1 1
type UnitScale "BMD" "cent" Source # 
Instance details
type UnitScale "BMD" "cent" = (,) 100 1
type UnitScale "BMD" "dollar" Source # 
Instance details
type UnitScale "BMD" "dollar" = (,) 1 1
type UnitScale "BND" "dollar" Source # 
Instance details
type UnitScale "BND" "dollar" = (,) 1 1
type UnitScale "BND" "sen" Source # 
Instance details
type UnitScale "BND" "sen" = (,) 100 1
type UnitScale "BOB" "boliviano" Source # 
Instance details
type UnitScale "BOB" "boliviano" = (,) 1 1
type UnitScale "BOB" "centavo" Source # 
Instance details
type UnitScale "BOB" "centavo" = (,) 100 1
type UnitScale "BRL" "centavo" Source # 
Instance details
type UnitScale "BRL" "centavo" = (,) 100 1
type UnitScale "BRL" "real" Source # 
Instance details
type UnitScale "BRL" "real" = (,) 1 1
type UnitScale "BSD" "cent" Source # 
Instance details
type UnitScale "BSD" "cent" = (,) 1 1
type UnitScale "BSD" "dollar" Source # 
Instance details
type UnitScale "BSD" "dollar" = (,) 1 1
type UnitScale "BTC" "bitcoin" Source # 
Instance details
type UnitScale "BTC" "bitcoin" = (,) 1 1
type UnitScale "BTC" "millibitcoin" Source # 
Instance details
type UnitScale "BTC" "millibitcoin" = (,) 1000 1
type UnitScale "BTC" "satoshi" Source # 
Instance details
type UnitScale "BTC" "satoshi" = (,) 100000000 1
type UnitScale "BTN" "chetrum" Source # 
Instance details
type UnitScale "BTN" "chetrum" = (,) 100 1
type UnitScale "BTN" "ngultrum" Source # 
Instance details
type UnitScale "BTN" "ngultrum" = (,) 1 1
type UnitScale "BWP" "pula" Source # 
Instance details
type UnitScale "BWP" "pula" = (,) 1 1
type UnitScale "BWP" "thebe" Source # 
Instance details
type UnitScale "BWP" "thebe" = (,) 100 1
type UnitScale "BYN" "kapiejka" Source # 
Instance details
type UnitScale "BYN" "kapiejka" = (,) 100 1
type UnitScale "BYN" "ruble" Source # 
Instance details
type UnitScale "BYN" "ruble" = (,) 1 1
type UnitScale "BYR" "kapiejka" Source # 
Instance details
type UnitScale "BYR" "kapiejka" = (,) 100 1
type UnitScale "BYR" "ruble" Source # 
Instance details
type UnitScale "BYR" "ruble" = (,) 1 1
type UnitScale "BZD" "cent" Source # 
Instance details
type UnitScale "BZD" "cent" = (,) 100 1
type UnitScale "BZD" "dollar" Source # 
Instance details
type UnitScale "BZD" "dollar" = (,) 1 1
type UnitScale "CAD" "cent" Source # 
Instance details
type UnitScale "CAD" "cent" = (,) 100 1
type UnitScale "CAD" "dollar" Source # 
Instance details
type UnitScale "CAD" "dollar" = (,) 1 1
type UnitScale "CDF" "centime" Source # 
Instance details
type UnitScale "CDF" "centime" = (,) 100 1
type UnitScale "CDF" "franc" Source # 
Instance details
type UnitScale "CDF" "franc" = (,) 1 1
type UnitScale "CHF" "franc" Source # 
Instance details
type UnitScale "CHF" "franc" = (,) 1 1
type UnitScale "CHF" "rappen" Source # 
Instance details
type UnitScale "CHF" "rappen" = (,) 100 1
type UnitScale "CLP" "centavo" Source # 
Instance details
type UnitScale "CLP" "centavo" = (,) 100 1
type UnitScale "CLP" "peso" Source # 
Instance details
type UnitScale "CLP" "peso" = (,) 1 1
type UnitScale "CNY" "fen" Source # 
Instance details
type UnitScale "CNY" "fen" = (,) 100 1
type UnitScale "CNY" "yuan" Source # 
Instance details
type UnitScale "CNY" "yuan" = (,) 1 1
type UnitScale "COP" "centavo" Source # 
Instance details
type UnitScale "COP" "centavo" = (,) 100 1
type UnitScale "COP" "peso" Source # 
Instance details
type UnitScale "COP" "peso" = (,) 1 1
type UnitScale "CRC" "centimo" Source # 
Instance details
type UnitScale "CRC" "centimo" = (,) 100 1
type UnitScale "CRC" "colon" Source # 
Instance details
type UnitScale "CRC" "colon" = (,) 1 1
type UnitScale "CUC" "centavo" Source # 
Instance details
type UnitScale "CUC" "centavo" = (,) 100 1
type UnitScale "CUC" "peso" Source # 
Instance details
type UnitScale "CUC" "peso" = (,) 1 1
type UnitScale "CUP" "centavo" Source # 
Instance details
type UnitScale "CUP" "centavo" = (,) 100 1
type UnitScale "CUP" "peso" Source # 
Instance details
type UnitScale "CUP" "peso" = (,) 1 1
type UnitScale "CVE" "centavo" Source # 
Instance details
type UnitScale "CVE" "centavo" = (,) 100 1
type UnitScale "CVE" "escudo" Source # 
Instance details
type UnitScale "CVE" "escudo" = (,) 1 1
type UnitScale "CZK" "haler" Source # 
Instance details
type UnitScale "CZK" "haler" = (,) 100 1
type UnitScale "CZK" "koruna" Source # 
Instance details
type UnitScale "CZK" "koruna" = (,) 1 1
type UnitScale "DJF" "centime" Source # 
Instance details
type UnitScale "DJF" "centime" = (,) 100 1
type UnitScale "DJF" "franc" Source # 
Instance details
type UnitScale "DJF" "franc" = (,) 1 1
type UnitScale "DKK" "krone" Source # 
Instance details
type UnitScale "DKK" "krone" = (,) 1 1
type UnitScale "DKK" "ore" Source # 
Instance details
type UnitScale "DKK" "ore" = (,) 100 1
type UnitScale "DOP" "centavo" Source # 
Instance details
type UnitScale "DOP" "centavo" = (,) 100 1
type UnitScale "DOP" "peso" Source # 
Instance details
type UnitScale "DOP" "peso" = (,) 1 1
type UnitScale "DZD" "dinar" Source # 
Instance details
type UnitScale "DZD" "dinar" = (,) 1 1
type UnitScale "DZD" "santeem" Source # 
Instance details
type UnitScale "DZD" "santeem" = (,) 100 1
type UnitScale "EGP" "piastre" Source # 
Instance details
type UnitScale "EGP" "piastre" = (,) 100 1
type UnitScale "EGP" "pound" Source # 
Instance details
type UnitScale "EGP" "pound" = (,) 1 1
type UnitScale "ERN" "cent" Source # 
Instance details
type UnitScale "ERN" "cent" = (,) 100 1
type UnitScale "ERN" "nafka" Source # 
Instance details
type UnitScale "ERN" "nafka" = (,) 1 1
type UnitScale "ETB" "birr" Source # 
Instance details
type UnitScale "ETB" "birr" = (,) 1 1
type UnitScale "ETB" "santim" Source # 
Instance details
type UnitScale "ETB" "santim" = (,) 100 1
type UnitScale "ETH" "babbage" Source # 
Instance details
type UnitScale "ETH" "babbage" = (,) 1000 1
type UnitScale "ETH" "ether" Source # 
Instance details
type UnitScale "ETH" "ether" = (,) 1 1
type UnitScale "ETH" "finney" Source # 
Instance details
type UnitScale "ETH" "finney" = (,) 1000000000000000 1
type UnitScale "ETH" "gwei" Source # 
Instance details
type UnitScale "ETH" "gwei" = (,) 1000000000 1
type UnitScale "ETH" "kwei" Source # 
Instance details
type UnitScale "ETH" "kwei" = (,) 1000 1
type UnitScale "ETH" "lovelace" Source # 
Instance details
type UnitScale "ETH" "lovelace" = (,) 1000000 1
type UnitScale "ETH" "microether" Source # 
Instance details
type UnitScale "ETH" "microether" = (,) 1000000000000 1
type UnitScale "ETH" "milliether" Source # 
Instance details
type UnitScale "ETH" "milliether" = (,) 1000000000000000 1
type UnitScale "ETH" "mwei" Source # 
Instance details
type UnitScale "ETH" "mwei" = (,) 1000000 1
type UnitScale "ETH" "shannon" Source # 
Instance details
type UnitScale "ETH" "shannon" = (,) 1000000000 1
type UnitScale "ETH" "szabo" Source # 
Instance details
type UnitScale "ETH" "szabo" = (,) 1000000000000 1
type UnitScale "ETH" "wei" Source # 
Instance details
type UnitScale "ETH" "wei" = (,) 1000000000000000000 1
type UnitScale "EUR" "cent" Source # 
Instance details
type UnitScale "EUR" "cent" = (,) 100 1
type UnitScale "EUR" "euro" Source # 
Instance details
type UnitScale "EUR" "euro" = (,) 1 1
type UnitScale "FJD" "cent" Source # 
Instance details
type UnitScale "FJD" "cent" = (,) 100 1
type UnitScale "FJD" "dollar" Source # 
Instance details
type UnitScale "FJD" "dollar" = (,) 1 1
type UnitScale "FKP" "penny" Source # 
Instance details
type UnitScale "FKP" "penny" = (,) 100 1
type UnitScale "FKP" "pound" Source # 
Instance details
type UnitScale "FKP" "pound" = (,) 1 1
type UnitScale "GBP" "penny" Source # 
Instance details
type UnitScale "GBP" "penny" = (,) 100 1
type UnitScale "GBP" "pound" Source # 
Instance details
type UnitScale "GBP" "pound" = (,) 1 1
type UnitScale "GEL" "lari" Source # 
Instance details
type UnitScale "GEL" "lari" = (,) 1 1
type UnitScale "GEL" "tetri" Source # 
Instance details
type UnitScale "GEL" "tetri" = (,) 100 1
type UnitScale "GHS" "cedi" Source # 
Instance details
type UnitScale "GHS" "cedi" = (,) 1 1
type UnitScale "GHS" "pesewa" Source # 
Instance details
type UnitScale "GHS" "pesewa" = (,) 100 1
type UnitScale "GIP" "penny" Source # 
Instance details
type UnitScale "GIP" "penny" = (,) 100 1
type UnitScale "GIP" "pound" Source # 
Instance details
type UnitScale "GIP" "pound" = (,) 1 1
type UnitScale "GMD" "butut" Source # 
Instance details
type UnitScale "GMD" "butut" = (,) 100 1
type UnitScale "GMD" "dalasi" Source # 
Instance details
type UnitScale "GMD" "dalasi" = (,) 1 1
type UnitScale "GNF" "centime" Source # 
Instance details
type UnitScale "GNF" "centime" = (,) 100 1
type UnitScale "GNF" "franc" Source # 
Instance details
type UnitScale "GNF" "franc" = (,) 1 1
type UnitScale "GTQ" "centavo" Source # 
Instance details
type UnitScale "GTQ" "centavo" = (,) 100 1
type UnitScale "GTQ" "quetzal" Source # 
Instance details
type UnitScale "GTQ" "quetzal" = (,) 1 1
type UnitScale "GYD" "cent" Source # 
Instance details
type UnitScale "GYD" "cent" = (,) 100 1
type UnitScale "GYD" "dollar" Source # 
Instance details
type UnitScale "GYD" "dollar" = (,) 1 1
type UnitScale "HKD" "cent" Source # 
Instance details
type UnitScale "HKD" "cent" = (,) 100 1
type UnitScale "HKD" "dollar" Source # 
Instance details
type UnitScale "HKD" "dollar" = (,) 1 1
type UnitScale "HNL" "centavo" Source # 
Instance details
type UnitScale "HNL" "centavo" = (,) 100 1
type UnitScale "HNL" "lempira" Source # 
Instance details
type UnitScale "HNL" "lempira" = (,) 1 1
type UnitScale "HRK" "kuna" Source # 
Instance details
type UnitScale "HRK" "kuna" = (,) 1 1
type UnitScale "HRK" "lipa" Source # 
Instance details
type UnitScale "HRK" "lipa" = (,) 100 1
type UnitScale "HTG" "centime" Source # 
Instance details
type UnitScale "HTG" "centime" = (,) 1 1
type UnitScale "HTG" "gourde" Source # 
Instance details
type UnitScale "HTG" "gourde" = (,) 1 1
type UnitScale "HUF" "filler" Source # 
Instance details
type UnitScale "HUF" "filler" = (,) 100 1
type UnitScale "HUF" "forint" Source # 
Instance details
type UnitScale "HUF" "forint" = (,) 1 1
type UnitScale "IDR" "rupiah" Source # 
Instance details
type UnitScale "IDR" "rupiah" = (,) 1 1
type UnitScale "IDR" "sen" Source # 
Instance details
type UnitScale "IDR" "sen" = (,) 100 1
type UnitScale "ILS" "agora" Source # 
Instance details
type UnitScale "ILS" "agora" = (,) 100 1
type UnitScale "ILS" "shekel" Source # 
Instance details
type UnitScale "ILS" "shekel" = (,) 1 1
type UnitScale "INR" "paisa" Source # 
Instance details
type UnitScale "INR" "paisa" = (,) 100 1
type UnitScale "INR" "rupee" Source # 
Instance details
type UnitScale "INR" "rupee" = (,) 1 1
type UnitScale "IQD" "dinar" Source # 
Instance details
type UnitScale "IQD" "dinar" = (,) 1 1
type UnitScale "IQD" "fils" Source # 
Instance details
type UnitScale "IQD" "fils" = (,) 1000 1
type UnitScale "IRR" "dinar" Source # 
Instance details
type UnitScale "IRR" "dinar" = (,) 100 1
type UnitScale "IRR" "rial" Source # 
Instance details
type UnitScale "IRR" "rial" = (,) 1 1
type UnitScale "ISK" "eyrir" Source # 
Instance details
type UnitScale "ISK" "eyrir" = (,) 100 1
type UnitScale "ISK" "krona" Source # 
Instance details
type UnitScale "ISK" "krona" = (,) 1 1
type UnitScale "JMD" "cent" Source # 
Instance details
type UnitScale "JMD" "cent" = (,) 100 1
type UnitScale "JMD" "dollar" Source # 
Instance details
type UnitScale "JMD" "dollar" = (,) 1 1
type UnitScale "JOD" "dinar" Source # 
Instance details
type UnitScale "JOD" "dinar" = (,) 1 1
type UnitScale "JOD" "piastre" Source # 
Instance details
type UnitScale "JOD" "piastre" = (,) 100 1
type UnitScale "JPY" "sen" Source # 
Instance details
type UnitScale "JPY" "sen" = (,) 100 1
type UnitScale "JPY" "yen" Source # 
Instance details
type UnitScale "JPY" "yen" = (,) 1 1
type UnitScale "KES" "cent" Source # 
Instance details
type UnitScale "KES" "cent" = (,) 100 1
type UnitScale "KES" "shilling" Source # 
Instance details
type UnitScale "KES" "shilling" = (,) 1 1
type UnitScale "KGS" "som" Source # 
Instance details
type UnitScale "KGS" "som" = (,) 1 1
type UnitScale "KGS" "tyiyn" Source # 
Instance details
type UnitScale "KGS" "tyiyn" = (,) 100 1
type UnitScale "KHR" "riel" Source # 
Instance details
type UnitScale "KHR" "riel" = (,) 1 1
type UnitScale "KHR" "sen" Source # 
Instance details
type UnitScale "KHR" "sen" = (,) 100 1
type UnitScale "KMF" "centime" Source # 
Instance details
type UnitScale "KMF" "centime" = (,) 100 1
type UnitScale "KMF" "franc" Source # 
Instance details
type UnitScale "KMF" "franc" = (,) 1 1
type UnitScale "KPW" "chon" Source # 
Instance details
type UnitScale "KPW" "chon" = (,) 100 1
type UnitScale "KPW" "won" Source # 
Instance details
type UnitScale "KPW" "won" = (,) 1 1
type UnitScale "KRW" "jeon" Source # 
Instance details
type UnitScale "KRW" "jeon" = (,) 100 1
type UnitScale "KRW" "won" Source # 
Instance details
type UnitScale "KRW" "won" = (,) 1 1
type UnitScale "KWD" "dinar" Source # 
Instance details
type UnitScale "KWD" "dinar" = (,) 1 1
type UnitScale "KWD" "fils" Source # 
Instance details
type UnitScale "KWD" "fils" = (,) 1000 1
type UnitScale "KYD" "cent" Source # 
Instance details
type UnitScale "KYD" "cent" = (,) 100 1
type UnitScale "KYD" "dollar" Source # 
Instance details
type UnitScale "KYD" "dollar" = (,) 1 1
type UnitScale "KZT" "tenge" Source # 
Instance details
type UnitScale "KZT" "tenge" = (,) 1 1
type UnitScale "KZT" "tiyin" Source # 
Instance details
type UnitScale "KZT" "tiyin" = (,) 100 1
type UnitScale "LAK" "att" Source # 
Instance details
type UnitScale "LAK" "att" = (,) 100 1
type UnitScale "LAK" "kip" Source # 
Instance details
type UnitScale "LAK" "kip" = (,) 1 1
type UnitScale "LBP" "piastre" Source # 
Instance details
type UnitScale "LBP" "piastre" = (,) 100 1
type UnitScale "LBP" "pound" Source # 
Instance details
type UnitScale "LBP" "pound" = (,) 1 1
type UnitScale "LKR" "cent" Source # 
Instance details
type UnitScale "LKR" "cent" = (,) 100 1
type UnitScale "LKR" "rupee" Source # 
Instance details
type UnitScale "LKR" "rupee" = (,) 1 1
type UnitScale "LRD" "cent" Source # 
Instance details
type UnitScale "LRD" "cent" = (,) 100 1
type UnitScale "LRD" "dollar" Source # 
Instance details
type UnitScale "LRD" "dollar" = (,) 1 1
type UnitScale "LSL" "loti" Source # 
Instance details
type UnitScale "LSL" "loti" = (,) 1 1
type UnitScale "LSL" "sente" Source # 
Instance details
type UnitScale "LSL" "sente" = (,) 100 1
type UnitScale "LTC" "lite" Source # 
Instance details
type UnitScale "LTC" "lite" = (,) 1000 1
type UnitScale "LTC" "litecoin" Source # 
Instance details
type UnitScale "LTC" "litecoin" = (,) 1 1
type UnitScale "LTC" "photon" Source # 
Instance details
type UnitScale "LTC" "photon" = (,) 100000000 1
type UnitScale "LYD" "dinar" Source # 
Instance details
type UnitScale "LYD" "dinar" = (,) 1 1
type UnitScale "LYD" "dirham" Source # 
Instance details
type UnitScale "LYD" "dirham" = (,) 1000 1
type UnitScale "MAD" "centime" Source # 
Instance details
type UnitScale "MAD" "centime" = (,) 100 1
type UnitScale "MAD" "dirham" Source # 
Instance details
type UnitScale "MAD" "dirham" = (,) 1 1
type UnitScale "MDL" "ban" Source # 
Instance details
type UnitScale "MDL" "ban" = (,) 100 1
type UnitScale "MDL" "leu" Source # 
Instance details
type UnitScale "MDL" "leu" = (,) 100 1
type UnitScale "MGA" "ariary" Source # 
Instance details
type UnitScale "MGA" "ariary" = (,) 1 1
type UnitScale "MGA" "iraimbilanja" Source # 
Instance details
type UnitScale "MGA" "iraimbilanja" = (,) 5 1
type UnitScale "MKD" "denar" Source # 
Instance details
type UnitScale "MKD" "denar" = (,) 1 1
type UnitScale "MKD" "deni" Source # 
Instance details
type UnitScale "MKD" "deni" = (,) 100 1
type UnitScale "MMK" "kyat" Source # 
Instance details
type UnitScale "MMK" "kyat" = (,) 1 1
type UnitScale "MMK" "pya" Source # 
Instance details
type UnitScale "MMK" "pya" = (,) 100 1
type UnitScale "MNT" "mongo" Source # 
Instance details
type UnitScale "MNT" "mongo" = (,) 100 1
type UnitScale "MNT" "tugrik" Source # 
Instance details
type UnitScale "MNT" "tugrik" = (,) 1 1
type UnitScale "MOP" "avo" Source # 
Instance details
type UnitScale "MOP" "avo" = (,) 100 1
type UnitScale "MOP" "pataca" Source # 
Instance details
type UnitScale "MOP" "pataca" = (,) 1 1
type UnitScale "MRO" "khoums" Source # 
Instance details
type UnitScale "MRO" "khoums" = (,) 5 1
type UnitScale "MRO" "ouguiya" Source # 
Instance details
type UnitScale "MRO" "ouguiya" = (,) 1 1
type UnitScale "MUR" "cent" Source # 
Instance details
type UnitScale "MUR" "cent" = (,) 100 1
type UnitScale "MUR" "rupee" Source # 
Instance details
type UnitScale "MUR" "rupee" = (,) 1 1
type UnitScale "MVR" "laari" Source # 
Instance details
type UnitScale "MVR" "laari" = (,) 100 1
type UnitScale "MVR" "rufiyaa" Source # 
Instance details
type UnitScale "MVR" "rufiyaa" = (,) 1 1
type UnitScale "MWK" "kwacha" Source # 
Instance details
type UnitScale "MWK" "kwacha" = (,) 1 1
type UnitScale "MWK" "tambala" Source # 
Instance details
type UnitScale "MWK" "tambala" = (,) 100 1
type UnitScale "MXN" "centavo" Source # 
Instance details
type UnitScale "MXN" "centavo" = (,) 100 1
type UnitScale "MXN" "peso" Source # 
Instance details
type UnitScale "MXN" "peso" = (,) 1 1
type UnitScale "MYR" "ringgit" Source # 
Instance details
type UnitScale "MYR" "ringgit" = (,) 1 1
type UnitScale "MYR" "sen" Source # 
Instance details
type UnitScale "MYR" "sen" = (,) 100 1
type UnitScale "MZN" "centavo" Source # 
Instance details
type UnitScale "MZN" "centavo" = (,) 100 1
type UnitScale "MZN" "metical" Source # 
Instance details
type UnitScale "MZN" "metical" = (,) 1 1
type UnitScale "NAD" "cent" Source # 
Instance details
type UnitScale "NAD" "cent" = (,) 100 1
type UnitScale "NAD" "dollar" Source # 
Instance details
type UnitScale "NAD" "dollar" = (,) 1 1
type UnitScale "NGN" "kobo" Source # 
Instance details
type UnitScale "NGN" "kobo" = (,) 100 1
type UnitScale "NGN" "naira" Source # 
Instance details
type UnitScale "NGN" "naira" = (,) 1 1
type UnitScale "NIO" "centavo" Source # 
Instance details
type UnitScale "NIO" "centavo" = (,) 100 1
type UnitScale "NIO" "cordoba" Source # 
Instance details
type UnitScale "NIO" "cordoba" = (,) 1 1
type UnitScale "NOK" "krone" Source # 
Instance details
type UnitScale "NOK" "krone" = (,) 1 1
type UnitScale "NOK" "ore" Source # 
Instance details
type UnitScale "NOK" "ore" = (,) 100 1
type UnitScale "NPR" "paisa" Source # 
Instance details
type UnitScale "NPR" "paisa" = (,) 100 1
type UnitScale "NPR" "rupee" Source # 
Instance details
type UnitScale "NPR" "rupee" = (,) 1 1
type UnitScale "NZD" "cent" Source # 
Instance details
type UnitScale "NZD" "cent" = (,) 100 1
type UnitScale "NZD" "dollar" Source # 
Instance details
type UnitScale "NZD" "dollar" = (,) 1 1
type UnitScale "OMR" "baisa" Source # 
Instance details
type UnitScale "OMR" "baisa" = (,) 1000 1
type UnitScale "OMR" "rial" Source # 
Instance details
type UnitScale "OMR" "rial" = (,) 1 1
type UnitScale "PAB" "balboa" Source # 
Instance details
type UnitScale "PAB" "balboa" = (,) 1 1
type UnitScale "PAB" "centesimo" Source # 
Instance details
type UnitScale "PAB" "centesimo" = (,) 100 1
type UnitScale "PEN" "centimo" Source # 
Instance details
type UnitScale "PEN" "centimo" = (,) 100 1
type UnitScale "PEN" "sol" Source # 
Instance details
type UnitScale "PEN" "sol" = (,) 1 1
type UnitScale "PGK" "kina" Source # 
Instance details
type UnitScale "PGK" "kina" = (,) 1 1
type UnitScale "PGK" "toea" Source # 
Instance details
type UnitScale "PGK" "toea" = (,) 100 1
type UnitScale "PHP" "centavo" Source # 
Instance details
type UnitScale "PHP" "centavo" = (,) 100 1
type UnitScale "PHP" "peso" Source # 
Instance details
type UnitScale "PHP" "peso" = (,) 1 1
type UnitScale "PKR" "paisa" Source # 
Instance details
type UnitScale "PKR" "paisa" = (,) 100 1
type UnitScale "PKR" "rupee" Source # 
Instance details
type UnitScale "PKR" "rupee" = (,) 1 1
type UnitScale "PLN" "grosz" Source # 
Instance details
type UnitScale "PLN" "grosz" = (,) 100 1
type UnitScale "PLN" "zloty" Source # 
Instance details
type UnitScale "PLN" "zloty" = (,) 1 1
type UnitScale "PYG" "centimo" Source # 
Instance details
type UnitScale "PYG" "centimo" = (,) 100 1
type UnitScale "PYG" "guarani" Source # 
Instance details
type UnitScale "PYG" "guarani" = (,) 1 1
type UnitScale "QAR" "dirham" Source # 
Instance details
type UnitScale "QAR" "dirham" = (,) 100 1
type UnitScale "QAR" "riyal" Source # 
Instance details
type UnitScale "QAR" "riyal" = (,) 1 1
type UnitScale "RON" "ban" Source # 
Instance details
type UnitScale "RON" "ban" = (,) 100 1
type UnitScale "RON" "leu" Source # 
Instance details
type UnitScale "RON" "leu" = (,) 1 1
type UnitScale "RSD" "dinar" Source # 
Instance details
type UnitScale "RSD" "dinar" = (,) 1 1
type UnitScale "RSD" "para" Source # 
Instance details
type UnitScale "RSD" "para" = (,) 100 1
type UnitScale "RUB" "kopek" Source # 
Instance details
type UnitScale "RUB" "kopek" = (,) 100 1
type UnitScale "RUB" "ruble" Source # 
Instance details
type UnitScale "RUB" "ruble" = (,) 1 1
type UnitScale "RWF" "centime" Source # 
Instance details
type UnitScale "RWF" "centime" = (,) 100 1
type UnitScale "RWF" "franc" Source # 
Instance details
type UnitScale "RWF" "franc" = (,) 1 1
type UnitScale "SAR" "halala" Source # 
Instance details
type UnitScale "SAR" "halala" = (,) 100 1
type UnitScale "SAR" "riyal" Source # 
Instance details
type UnitScale "SAR" "riyal" = (,) 1 1
type UnitScale "SBD" "cent" Source # 
Instance details
type UnitScale "SBD" "cent" = (,) 100 1
type UnitScale "SBD" "dollar" Source # 
Instance details
type UnitScale "SBD" "dollar" = (,) 100 1
type UnitScale "SCR" "cent" Source # 
Instance details
type UnitScale "SCR" "cent" = (,) 100 1
type UnitScale "SCR" "rupee" Source # 
Instance details
type UnitScale "SCR" "rupee" = (,) 1 1
type UnitScale "SDG" "piastre" Source # 
Instance details
type UnitScale "SDG" "piastre" = (,) 100 1
type UnitScale "SDG" "pound" Source # 
Instance details
type UnitScale "SDG" "pound" = (,) 1 1
type UnitScale "SEK" "krona" Source # 
Instance details
type UnitScale "SEK" "krona" = (,) 1 1
type UnitScale "SEK" "ore" Source # 
Instance details
type UnitScale "SEK" "ore" = (,) 100 1
type UnitScale "SGD" "cent" Source # 
Instance details
type UnitScale "SGD" "cent" = (,) 100 1
type UnitScale "SGD" "dollar" Source # 
Instance details
type UnitScale "SGD" "dollar" = (,) 1 1
type UnitScale "SHP" "penny" Source # 
Instance details
type UnitScale "SHP" "penny" = (,) 100 1
type UnitScale "SHP" "pound" Source # 
Instance details
type UnitScale "SHP" "pound" = (,) 1 1
type UnitScale "SLL" "cent" Source # 
Instance details
type UnitScale "SLL" "cent" = (,) 100 1
type UnitScale "SLL" "leone" Source # 
Instance details
type UnitScale "SLL" "leone" = (,) 1 1
type UnitScale "SOS" "cent" Source # 
Instance details
type UnitScale "SOS" "cent" = (,) 100 1
type UnitScale "SOS" "shilling" Source # 
Instance details
type UnitScale "SOS" "shilling" = (,) 1 1
type UnitScale "SRD" "cent" Source # 
Instance details
type UnitScale "SRD" "cent" = (,) 100 1
type UnitScale "SRD" "dollar" Source # 
Instance details
type UnitScale "SRD" "dollar" = (,) 1 1
type UnitScale "SSP" "piastre" Source # 
Instance details
type UnitScale "SSP" "piastre" = (,) 100 1
type UnitScale "SSP" "pound" Source # 
Instance details
type UnitScale "SSP" "pound" = (,) 1 1
type UnitScale "STD" "centimo" Source # 
Instance details
type UnitScale "STD" "centimo" = (,) 100 1
type UnitScale "STD" "dobra" Source # 
Instance details
type UnitScale "STD" "dobra" = (,) 1 1
type UnitScale "SVC" "centavo" Source # 
Instance details
type UnitScale "SVC" "centavo" = (,) 100 1
type UnitScale "SVC" "colon" Source # 
Instance details
type UnitScale "SVC" "colon" = (,) 1 1
type UnitScale "SYP" "piastre" Source # 
Instance details
type UnitScale "SYP" "piastre" = (,) 100 1
type UnitScale "SYP" "pound" Source # 
Instance details
type UnitScale "SYP" "pound" = (,) 1 1
type UnitScale "SZL" "cent" Source # 
Instance details
type UnitScale "SZL" "cent" = (,) 100 1
type UnitScale "SZL" "lilangeni" Source # 
Instance details
type UnitScale "SZL" "lilangeni" = (,) 1 1
type UnitScale "THB" "baht" Source # 
Instance details
type UnitScale "THB" "baht" = (,) 1 1
type UnitScale "THB" "satang" Source # 
Instance details
type UnitScale "THB" "satang" = (,) 100 1
type UnitScale "TJS" "diram" Source # 
Instance details
type UnitScale "TJS" "diram" = (,) 100 1
type UnitScale "TJS" "somoni" Source # 
Instance details
type UnitScale "TJS" "somoni" = (,) 1 1
type UnitScale "TMT" "manat" Source # 
Instance details
type UnitScale "TMT" "manat" = (,) 1 1
type UnitScale "TMT" "tennesi" Source # 
Instance details
type UnitScale "TMT" "tennesi" = (,) 100 1
type UnitScale "TND" "dinar" Source # 
Instance details
type UnitScale "TND" "dinar" = (,) 1 1
type UnitScale "TND" "millime" Source # 
Instance details
type UnitScale "TND" "millime" = (,) 1000 1
type UnitScale "TOP" "pa'anga" Source # 
Instance details
type UnitScale "TOP" "pa'anga" = (,) 1 1
type UnitScale "TOP" "seniti" Source # 
Instance details
type UnitScale "TOP" "seniti" = (,) 100 1
type UnitScale "TRY" "kurus" Source # 
Instance details
type UnitScale "TRY" "kurus" = (,) 100 1
type UnitScale "TRY" "lira" Source # 
Instance details
type UnitScale "TRY" "lira" = (,) 1 1
type UnitScale "TTD" "cent" Source # 
Instance details
type UnitScale "TTD" "cent" = (,) 100 1
type UnitScale "TTD" "dollar" Source # 
Instance details
type UnitScale "TTD" "dollar" = (,) 1 1
type UnitScale "TWD" "cent" Source # 
Instance details
type UnitScale "TWD" "cent" = (,) 100 1
type UnitScale "TWD" "dollar" Source # 
Instance details
type UnitScale "TWD" "dollar" = (,) 1 1
type UnitScale "TZS" "cent" Source # 
Instance details
type UnitScale "TZS" "cent" = (,) 100 1
type UnitScale "TZS" "shilling" Source # 
Instance details
type UnitScale "TZS" "shilling" = (,) 1 1
type UnitScale "UAH" "hryvnia" Source # 
Instance details
type UnitScale "UAH" "hryvnia" = (,) 1 1
type UnitScale "UAH" "kopiyka" Source # 
Instance details
type UnitScale "UAH" "kopiyka" = (,) 100 1
type UnitScale "UGX" "cent" Source # 
Instance details
type UnitScale "UGX" "cent" = (,) 100 1
type UnitScale "UGX" "shilling" Source # 
Instance details
type UnitScale "UGX" "shilling" = (,) 1 1
type UnitScale "USD" "cent" Source # 
Instance details
type UnitScale "USD" "cent" = (,) 100 1
type UnitScale "USD" "dollar" Source # 
Instance details
type UnitScale "USD" "dollar" = (,) 1 1
type UnitScale "USN" "cent" Source # 
Instance details
type UnitScale "USN" "cent" = (,) 100 1
type UnitScale "USN" "dollar" Source # 
Instance details
type UnitScale "USN" "dollar" = (,) 1 1
type UnitScale "UYU" "centesimo" Source # 
Instance details
type UnitScale "UYU" "centesimo" = (,) 100 1
type UnitScale "UYU" "peso" Source # 
Instance details
type UnitScale "UYU" "peso" = (,) 1 1
type UnitScale "UZS" "som" Source # 
Instance details
type UnitScale "UZS" "som" = (,) 1 1
type UnitScale "UZS" "tiyin" Source # 
Instance details
type UnitScale "UZS" "tiyin" = (,) 100 1
type UnitScale "VEF" "bolivar" Source # 
Instance details
type UnitScale "VEF" "bolivar" = (,) 1 1
type UnitScale "VEF" "centimo" Source # 
Instance details
type UnitScale "VEF" "centimo" = (,) 100 1
type UnitScale "VES" "bolivar" Source # 
Instance details
type UnitScale "VES" "bolivar" = (,) 1 1
type UnitScale "VES" "centimo" Source # 
Instance details
type UnitScale "VES" "centimo" = (,) 100 1
type UnitScale "VND" "dong" Source # 
Instance details
type UnitScale "VND" "dong" = (,) 1 1
type UnitScale "VND" "hao" Source # 
Instance details
type UnitScale "VND" "hao" = (,) 10 1
type UnitScale "VUV" "vatu" Source # 
Instance details
type UnitScale "VUV" "vatu" = (,) 1 1
type UnitScale "WST" "sene" Source # 
Instance details
type UnitScale "WST" "sene" = (,) 100 1
type UnitScale "WST" "tala" Source # 
Instance details
type UnitScale "WST" "tala" = (,) 1 1
type UnitScale "XAF" "centime" Source # 
Instance details
type UnitScale "XAF" "centime" = (,) 100 1
type UnitScale "XAF" "franc" Source # 
Instance details
type UnitScale "XAF" "franc" = (,) 1 1
type UnitScale "XAG" "grain" Source # 
Instance details
type UnitScale "XAG" "grain" = (,) 480 1
type UnitScale "XAG" "gram" Source # 
Instance details
type UnitScale "XAG" "gram" = (,) 31103477 1000000
type UnitScale "XAG" "kilogram" Source # 
Instance details
type UnitScale "XAG" "kilogram" = (,) 31103477 1000000000
type UnitScale "XAG" "micrograin" Source # 
Instance details
type UnitScale "XAG" "micrograin" = (,) 480000000 1
type UnitScale "XAG" "microgram" Source # 
Instance details
type UnitScale "XAG" "microgram" = (,) 31103477 1
type UnitScale "XAG" "milligrain" Source # 
Instance details
type UnitScale "XAG" "milligrain" = (,) 480000 1
type UnitScale "XAG" "milligram" Source # 
Instance details
type UnitScale "XAG" "milligram" = (,) 31103477 1000
type UnitScale "XAG" "troy-ounce" Source # 
Instance details
type UnitScale "XAG" "troy-ounce" = (,) 1 1
type UnitScale "XAU" "grain" Source # 
Instance details
type UnitScale "XAU" "grain" = (,) 480 1
type UnitScale "XAU" "gram" Source # 
Instance details
type UnitScale "XAU" "gram" = (,) 31103477 1000000
type UnitScale "XAU" "kilogram" Source # 
Instance details
type UnitScale "XAU" "kilogram" = (,) 31103477 1000000000
type UnitScale "XAU" "micrograin" Source # 
Instance details
type UnitScale "XAU" "micrograin" = (,) 480000000 1
type UnitScale "XAU" "microgram" Source # 
Instance details
type UnitScale "XAU" "microgram" = (,) 31103477 1
type UnitScale "XAU" "milligrain" Source # 
Instance details
type UnitScale "XAU" "milligrain" = (,) 480000 1
type UnitScale "XAU" "milligram" Source # 
Instance details
type UnitScale "XAU" "milligram" = (,) 31103477 1000
type UnitScale "XAU" "troy-ounce" Source # 
Instance details
type UnitScale "XAU" "troy-ounce" = (,) 1 1
type UnitScale "XBT" "bitcoin" Source # 
Instance details
type UnitScale "XBT" "bitcoin" = UnitScale "BTC" "bitcoin"
type UnitScale "XBT" "millibitcoin" Source # 
Instance details
type UnitScale "XBT" "millibitcoin" = UnitScale "BTC" "millibitcoin"
type UnitScale "XBT" "satoshi" Source # 
Instance details
type UnitScale "XBT" "satoshi" = UnitScale "BTC" "satoshi"
type UnitScale "XCD" "cent" Source # 
Instance details
type UnitScale "XCD" "cent" = (,) 100 1
type UnitScale "XCD" "dollar" Source # 
Instance details
type UnitScale "XCD" "dollar" = (,) 1 1
type UnitScale "XMR" "centinero" Source # 
Instance details
type UnitScale "XMR" "centinero" = (,) 100 1
type UnitScale "XMR" "decinero" Source # 
Instance details
type UnitScale "XMR" "decinero" = (,) 10 1
type UnitScale "XMR" "micronero" Source # 
Instance details
type UnitScale "XMR" "micronero" = (,) 1000000 1
type UnitScale "XMR" "millinero" Source # 
Instance details
type UnitScale "XMR" "millinero" = (,) 1000 1
type UnitScale "XMR" "monero" Source # 
Instance details
type UnitScale "XMR" "monero" = (,) 1 1
type UnitScale "XMR" "nanonero" Source # 
Instance details
type UnitScale "XMR" "nanonero" = (,) 1000000000 1
type UnitScale "XMR" "piconero" Source # 
Instance details
type UnitScale "XMR" "piconero" = (,) 1000000000000 1
type UnitScale "XOF" "centime" Source # 
Instance details
type UnitScale "XOF" "centime" = (,) 100 1
type UnitScale "XOF" "franc" Source # 
Instance details
type UnitScale "XOF" "franc" = (,) 1 1
type UnitScale "XPD" "grain" Source # 
Instance details
type UnitScale "XPD" "grain" = (,) 480 1
type UnitScale "XPD" "gram" Source # 
Instance details
type UnitScale "XPD" "gram" = (,) 31103477 1000000
type UnitScale "XPD" "kilogram" Source # 
Instance details
type UnitScale "XPD" "kilogram" = (,) 31103477 1000000000
type UnitScale "XPD" "micrograin" Source # 
Instance details
type UnitScale "XPD" "micrograin" = (,) 480000000 1
type UnitScale "XPD" "microgram" Source # 
Instance details
type UnitScale "XPD" "microgram" = (,) 31103477 1
type UnitScale "XPD" "milligrain" Source # 
Instance details
type UnitScale "XPD" "milligrain" = (,) 480000 1
type UnitScale "XPD" "milligram" Source # 
Instance details
type UnitScale "XPD" "milligram" = (,) 31103477 1000
type UnitScale "XPD" "troy-ounce" Source # 
Instance details
type UnitScale "XPD" "troy-ounce" = (,) 1 1
type UnitScale "XPF" "centime" Source # 
Instance details
type UnitScale "XPF" "centime" = (,) 100 1
type UnitScale "XPF" "franc" Source # 
Instance details
type UnitScale "XPF" "franc" = (,) 1 1
type UnitScale "XPT" "grain" Source # 
Instance details
type UnitScale "XPT" "grain" = (,) 480 1
type UnitScale "XPT" "gram" Source # 
Instance details
type UnitScale "XPT" "gram" = (,) 31103477 1000000
type UnitScale "XPT" "kilogram" Source # 
Instance details
type UnitScale "XPT" "kilogram" = (,) 31103477 1000000000
type UnitScale "XPT" "micrograin" Source # 
Instance details
type UnitScale "XPT" "micrograin" = (,) 480000000 1
type UnitScale "XPT" "microgram" Source # 
Instance details
type UnitScale "XPT" "microgram" = (,) 31103477 1
type UnitScale "XPT" "milligrain" Source # 
Instance details
type UnitScale "XPT" "milligrain" = (,) 480000 1
type UnitScale "XPT" "milligram" Source # 
Instance details
type UnitScale "XPT" "milligram" = (,) 31103477 1000
type UnitScale "XPT" "troy-ounce" Source # 
Instance details
type UnitScale "XPT" "troy-ounce" = (,) 1 1
type UnitScale "XRP" "drop" Source # 
Instance details
type UnitScale "XRP" "drop" = (,) 1000000 1
type UnitScale "XRP" "ripple" Source # 
Instance details
type UnitScale "XRP" "ripple" = (,) 1 1
type UnitScale "YER" "fils" Source # 
Instance details
type UnitScale "YER" "fils" = (,) 100 1
type UnitScale "YER" "rial" Source # 
Instance details
type UnitScale "YER" "rial" = (,) 1 1
type UnitScale "ZAR" "cent" Source # 
Instance details
type UnitScale "ZAR" "cent" = (,) 100 1
type UnitScale "ZAR" "rand" Source # 
Instance details
type UnitScale "ZAR" "rand" = (,) 1 1
type UnitScale "ZMW" "kwacha" Source # 
Instance details
type UnitScale "ZMW" "kwacha" = (,) 1 1
type UnitScale "ZMW" "ngwee" Source # 
Instance details
type UnitScale "ZMW" "ngwee" = (,) 100 1
type UnitScale "ZWL" "cent" Source # 
Instance details
type UnitScale "ZWL" "cent" = (,) 100 1
type UnitScale "ZWL" "dollar" Source # 
Instance details
type UnitScale "ZWL" "dollar" = (,) 1 1

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 CurrencyScale currency will return such Scale. For example, CurrencyScale "USD" evaluates to UnitScale "USD" "cent".

type instance CurrencyScale "USD" = UnitScale "USD" "cent"

If the currency doesn't have a canonical smallest Scale, then CurrencyScale currency shall be left undefined or fail to compile with a TypeError. For example CurrencyScale "XAU" fails with ErrScaleNonCanonical "XAU".

Instances
type CurrencyScale "ADA" Source # 
Instance details
type CurrencyScale "ADA" = UnitScale "ADA" "lovelace"
type CurrencyScale "AED" Source # 
Instance details
type CurrencyScale "AED" = UnitScale "AED" "fils"
type CurrencyScale "AFN" Source # 
Instance details
type CurrencyScale "AFN" = UnitScale "AFN" "pul"
type CurrencyScale "ALL" Source # 
Instance details
type CurrencyScale "ALL" = UnitScale "ALL" "lek"
type CurrencyScale "AMD" Source # 
Instance details
type CurrencyScale "AMD" = UnitScale "AMD" "luma"
type CurrencyScale "ANG" Source # 
Instance details
type CurrencyScale "ANG" = UnitScale "AMD" "cent"
type CurrencyScale "AOA" Source # 
Instance details
type CurrencyScale "AOA" = UnitScale "AOA" "centimo"
type CurrencyScale "ARS" Source # 
Instance details
type CurrencyScale "ARS" = UnitScale "ARS" "centavo"
type CurrencyScale "AUD" Source # 
Instance details
type CurrencyScale "AUD" = UnitScale "AUD" "cent"
type CurrencyScale "AWG" Source # 
Instance details
type CurrencyScale "AWG" = UnitScale "AWG" "cent"
type CurrencyScale "AZN" Source # 
Instance details
type CurrencyScale "AZN" = UnitScale "AZN" "qapik"
type CurrencyScale "BAM" Source # 
Instance details
type CurrencyScale "BAM" = UnitScale "BAM" "fenig"
type CurrencyScale "BBD" Source # 
Instance details
type CurrencyScale "BBD" = UnitScale "BBD" "cent"
type CurrencyScale "BDT" Source # 
Instance details
type CurrencyScale "BDT" = UnitScale "BDT" "paisa"
type CurrencyScale "BGN" Source # 
Instance details
type CurrencyScale "BGN" = UnitScale "BGN" "stotinka"
type CurrencyScale "BHD" Source # 
Instance details
type CurrencyScale "BHD" = UnitScale "BHD" "fils"
type CurrencyScale "BIF" Source # 
Instance details
type CurrencyScale "BIF" = UnitScale "BIF" "centime"
type CurrencyScale "BMD" Source # 
Instance details
type CurrencyScale "BMD" = UnitScale "BMD" "cent"
type CurrencyScale "BND" Source # 
Instance details
type CurrencyScale "BND" = UnitScale "BND" "sen"
type CurrencyScale "BOB" Source # 
Instance details
type CurrencyScale "BOB" = UnitScale "BOB" "centavo"
type CurrencyScale "BOV" Source # 
Instance details
type CurrencyScale "BOV" = (,) 100 1
type CurrencyScale "BRL" Source # 
Instance details
type CurrencyScale "BRL" = UnitScale "BRL" "centavo"
type CurrencyScale "BSD" Source # 
Instance details
type CurrencyScale "BSD" = UnitScale "BSD" "cent"
type CurrencyScale "BTC" Source # 
Instance details
type CurrencyScale "BTC" = UnitScale "BTC" "satoshi"
type CurrencyScale "BTN" Source # 
Instance details
type CurrencyScale "BTN" = UnitScale "BTN" "chetrum"
type CurrencyScale "BWP" Source # 
Instance details
type CurrencyScale "BWP" = UnitScale "BWP" "thebe"
type CurrencyScale "BYN" Source # 
Instance details
type CurrencyScale "BYN" = UnitScale "BYN" "kapiejka"
type CurrencyScale "BYR" Source # 
Instance details
type CurrencyScale "BYR" = UnitScale "BYR" "kapiejka"
type CurrencyScale "BZD" Source # 
Instance details
type CurrencyScale "BZD" = UnitScale "BZD" "cent"
type CurrencyScale "CAD" Source # 
Instance details
type CurrencyScale "CAD" = UnitScale "CAD" "cent"
type CurrencyScale "CDF" Source # 
Instance details
type CurrencyScale "CDF" = UnitScale "CDF" "centime"
type CurrencyScale "CHE" Source # 
Instance details
type CurrencyScale "CHE" = (,) 100 1
type CurrencyScale "CHF" Source # 
Instance details
type CurrencyScale "CHF" = UnitScale "CHF" "rappen"
type CurrencyScale "CHW" Source # 
Instance details
type CurrencyScale "CHW" = (,) 100 1
type CurrencyScale "CLF" Source # 
Instance details
type CurrencyScale "CLF" = (,) 10000 1
type CurrencyScale "CLP" Source # 
Instance details
type CurrencyScale "CLP" = UnitScale "CLP" "centavo"
type CurrencyScale "CNY" Source # 
Instance details
type CurrencyScale "CNY" = UnitScale "CNY" "fen"
type CurrencyScale "COP" Source # 
Instance details
type CurrencyScale "COP" = UnitScale "COP" "centavo"
type CurrencyScale "COU" Source # 
Instance details
type CurrencyScale "COU" = (,) 100 1
type CurrencyScale "CRC" Source # 
Instance details
type CurrencyScale "CRC" = UnitScale "CRC" "centimo"
type CurrencyScale "CUC" Source # 
Instance details
type CurrencyScale "CUC" = UnitScale "CUC" "centavo"
type CurrencyScale "CUP" Source # 
Instance details
type CurrencyScale "CUP" = UnitScale "CUP" "centavo"
type CurrencyScale "CVE" Source # 
Instance details
type CurrencyScale "CVE" = UnitScale "CVE" "centavo"
type CurrencyScale "CZK" Source # 
Instance details
type CurrencyScale "CZK" = UnitScale "CZK" "haler"
type CurrencyScale "DJF" Source # 
Instance details
type CurrencyScale "DJF" = UnitScale "DJF" "centime"
type CurrencyScale "DKK" Source # 
Instance details
type CurrencyScale "DKK" = UnitScale "DKK" "ore"
type CurrencyScale "DOP" Source # 
Instance details
type CurrencyScale "DOP" = UnitScale "DOP" "centavo"
type CurrencyScale "DZD" Source # 
Instance details
type CurrencyScale "DZD" = UnitScale "DZD" "santeem"
type CurrencyScale "EGP" Source # 
Instance details
type CurrencyScale "EGP" = UnitScale "EGP" "piastre"
type CurrencyScale "ERN" Source # 
Instance details
type CurrencyScale "ERN" = UnitScale "ERN" "cent"
type CurrencyScale "ETB" Source # 
Instance details
type CurrencyScale "ETB" = UnitScale "ETB" "santim"
type CurrencyScale "ETH" Source # 
Instance details
type CurrencyScale "ETH" = UnitScale "ETH" "wei"
type CurrencyScale "EUR" Source # 
Instance details
type CurrencyScale "EUR" = UnitScale "EUR" "cent"
type CurrencyScale "FJD" Source # 
Instance details
type CurrencyScale "FJD" = UnitScale "FJD" "cent"
type CurrencyScale "FKP" Source # 
Instance details
type CurrencyScale "FKP" = UnitScale "FKP" "penny"
type CurrencyScale "GBP" Source # 
Instance details
type CurrencyScale "GBP" = UnitScale "GBP" "penny"
type CurrencyScale "GEL" Source # 
Instance details
type CurrencyScale "GEL" = UnitScale "GEL" "tetri"
type CurrencyScale "GHS" Source # 
Instance details
type CurrencyScale "GHS" = UnitScale "GHS" "pesewa"
type CurrencyScale "GIP" Source # 
Instance details
type CurrencyScale "GIP" = UnitScale "GIP" "penny"
type CurrencyScale "GMD" Source # 
Instance details
type CurrencyScale "GMD" = UnitScale "GMD" "butut"
type CurrencyScale "GNF" Source # 
Instance details
type CurrencyScale "GNF" = UnitScale "GNF" "centime"
type CurrencyScale "GTQ" Source # 
Instance details
type CurrencyScale "GTQ" = UnitScale "GTQ" "centavo"
type CurrencyScale "GYD" Source # 
Instance details
type CurrencyScale "GYD" = UnitScale "GYD" "cent"
type CurrencyScale "HKD" Source # 
Instance details
type CurrencyScale "HKD" = UnitScale "HKD" "cent"
type CurrencyScale "HNL" Source # 
Instance details
type CurrencyScale "HNL" = UnitScale "HNL" "centavo"
type CurrencyScale "HRK" Source # 
Instance details
type CurrencyScale "HRK" = UnitScale "HRK" "lipa"
type CurrencyScale "HTG" Source # 
Instance details
type CurrencyScale "HTG" = UnitScale "HTG" "centime"
type CurrencyScale "HUF" Source # 
Instance details
type CurrencyScale "HUF" = UnitScale "HUF" "filler"
type CurrencyScale "IDR" Source # 
Instance details
type CurrencyScale "IDR" = UnitScale "IDR" "sen"
type CurrencyScale "ILS" Source # 
Instance details
type CurrencyScale "ILS" = UnitScale "ILS" "agora"
type CurrencyScale "INR" Source # 
Instance details
type CurrencyScale "INR" = UnitScale "INR" "paisa"
type CurrencyScale "IQD" Source # 
Instance details
type CurrencyScale "IQD" = UnitScale "IQD" "fils"
type CurrencyScale "IRR" Source # 
Instance details
type CurrencyScale "IRR" = UnitScale "IRR" "dinar"
type CurrencyScale "ISK" Source # 
Instance details
type CurrencyScale "ISK" = UnitScale "ISK" "eyrir"
type CurrencyScale "JMD" Source # 
Instance details
type CurrencyScale "JMD" = UnitScale "JMD" "cent"
type CurrencyScale "JOD" Source # 
Instance details
type CurrencyScale "JOD" = UnitScale "JOD" "piastre"
type CurrencyScale "JPY" Source # 
Instance details
type CurrencyScale "JPY" = UnitScale "JPY" "sen"
type CurrencyScale "KES" Source # 
Instance details
type CurrencyScale "KES" = UnitScale "KES" "cent"
type CurrencyScale "KGS" Source # 
Instance details
type CurrencyScale "KGS" = UnitScale "KGS" "tyiyn"
type CurrencyScale "KHR" Source # 
Instance details
type CurrencyScale "KHR" = UnitScale "KHR" "sen"
type CurrencyScale "KMF" Source # 
Instance details
type CurrencyScale "KMF" = UnitScale "KMF" "centime"
type CurrencyScale "KPW" Source # 
Instance details
type CurrencyScale "KPW" = UnitScale "KPW" "chon"
type CurrencyScale "KRW" Source # 
Instance details
type CurrencyScale "KRW" = UnitScale "KRW" "jeon"
type CurrencyScale "KWD" Source # 
Instance details
type CurrencyScale "KWD" = UnitScale "KWD" "fils"
type CurrencyScale "KYD" Source # 
Instance details
type CurrencyScale "KYD" = UnitScale "KYD" "cent"
type CurrencyScale "KZT" Source # 
Instance details
type CurrencyScale "KZT" = UnitScale "KZT" "tiyin"
type CurrencyScale "LAK" Source # 
Instance details
type CurrencyScale "LAK" = UnitScale "LAK" "att"
type CurrencyScale "LBP" Source # 
Instance details
type CurrencyScale "LBP" = UnitScale "LBP" "piastre"
type CurrencyScale "LKR" Source # 
Instance details
type CurrencyScale "LKR" = UnitScale "LKR" "cent"
type CurrencyScale "LRD" Source # 
Instance details
type CurrencyScale "LRD" = UnitScale "LRD" "cent"
type CurrencyScale "LSL" Source # 
Instance details
type CurrencyScale "LSL" = UnitScale "LSL" "sente"
type CurrencyScale "LTC" Source # 
Instance details
type CurrencyScale "LTC" = UnitScale "LTC" "photon"
type CurrencyScale "LYD" Source # 
Instance details
type CurrencyScale "LYD" = UnitScale "LYD" "dirham"
type CurrencyScale "MAD" Source # 
Instance details
type CurrencyScale "MAD" = UnitScale "MAD" "centime"
type CurrencyScale "MDL" Source # 
Instance details
type CurrencyScale "MDL" = UnitScale "MDL" "ban"
type CurrencyScale "MGA" Source # 
Instance details
type CurrencyScale "MGA" = UnitScale "MGA" "iraimbilanja"
type CurrencyScale "MKD" Source # 
Instance details
type CurrencyScale "MKD" = UnitScale "MKD" "deni"
type CurrencyScale "MMK" Source # 
Instance details
type CurrencyScale "MMK" = UnitScale "MMK" "pya"
type CurrencyScale "MNT" Source # 
Instance details
type CurrencyScale "MNT" = UnitScale "MNT" "mongo"
type CurrencyScale "MOP" Source # 
Instance details
type CurrencyScale "MOP" = UnitScale "MOP" "avo"
type CurrencyScale "MRO" Source # 
Instance details
type CurrencyScale "MRO" = UnitScale "MRO" "khoums"
type CurrencyScale "MUR" Source # 
Instance details
type CurrencyScale "MUR" = UnitScale "MUR" "cent"
type CurrencyScale "MVR" Source # 
Instance details
type CurrencyScale "MVR" = UnitScale "MVR" "laari"
type CurrencyScale "MWK" Source # 
Instance details
type CurrencyScale "MWK" = UnitScale "MWK" "tambala"
type CurrencyScale "MXN" Source # 
Instance details
type CurrencyScale "MXN" = UnitScale "MXN" "centavo"
type CurrencyScale "MXV" Source # 
Instance details
type CurrencyScale "MXV" = (,) 100 1
type CurrencyScale "MYR" Source # 
Instance details
type CurrencyScale "MYR" = UnitScale "MYR" "sen"
type CurrencyScale "MZN" Source # 
Instance details
type CurrencyScale "MZN" = UnitScale "MZN" "centavo"
type CurrencyScale "NAD" Source # 
Instance details
type CurrencyScale "NAD" = UnitScale "NAD" "cent"
type CurrencyScale "NGN" Source # 
Instance details
type CurrencyScale "NGN" = UnitScale "NGN" "kobo"
type CurrencyScale "NIO" Source # 
Instance details
type CurrencyScale "NIO" = UnitScale "NIO" "centavo"
type CurrencyScale "NOK" Source # 
Instance details
type CurrencyScale "NOK" = UnitScale "NOK" "ore"
type CurrencyScale "NPR" Source # 
Instance details
type CurrencyScale "NPR" = UnitScale "NPR" "paisa"
type CurrencyScale "NZD" Source # 
Instance details
type CurrencyScale "NZD" = UnitScale "NZD" "cent"
type CurrencyScale "OMR" Source # 
Instance details
type CurrencyScale "OMR" = UnitScale "OMR" "baisa"
type CurrencyScale "PAB" Source # 
Instance details
type CurrencyScale "PAB" = UnitScale "PAB" "centesimo"
type CurrencyScale "PEN" Source # 
Instance details
type CurrencyScale "PEN" = UnitScale "PEN" "centimo"
type CurrencyScale "PGK" Source # 
Instance details
type CurrencyScale "PGK" = UnitScale "PGK" "toea"
type CurrencyScale "PHP" Source # 
Instance details
type CurrencyScale "PHP" = UnitScale "PHP" "centavo"
type CurrencyScale "PKR" Source # 
Instance details
type CurrencyScale "PKR" = UnitScale "PKR" "paisa"
type CurrencyScale "PLN" Source # 
Instance details
type CurrencyScale "PLN" = UnitScale "PLN" "grosz"
type CurrencyScale "PYG" Source # 
Instance details
type CurrencyScale "PYG" = UnitScale "PYG" "centimo"
type CurrencyScale "QAR" Source # 
Instance details
type CurrencyScale "QAR" = UnitScale "QAR" "dirham"
type CurrencyScale "RON" Source # 
Instance details
type CurrencyScale "RON" = UnitScale "RON" "ban"
type CurrencyScale "RSD" Source # 
Instance details
type CurrencyScale "RSD" = UnitScale "RSD" "para"
type CurrencyScale "RUB" Source # 
Instance details
type CurrencyScale "RUB" = UnitScale "RUB" "kopek"
type CurrencyScale "RWF" Source # 
Instance details
type CurrencyScale "RWF" = UnitScale "RWF" "centime"
type CurrencyScale "SAR" Source # 
Instance details
type CurrencyScale "SAR" = UnitScale "SAR" "halala"
type CurrencyScale "SBD" Source # 
Instance details
type CurrencyScale "SBD" = UnitScale "SBD" "cent"
type CurrencyScale "SCR" Source # 
Instance details
type CurrencyScale "SCR" = UnitScale "SCR" "cent"
type CurrencyScale "SDG" Source # 
Instance details
type CurrencyScale "SDG" = UnitScale "SDG" "piastre"
type CurrencyScale "SEK" Source # 
Instance details
type CurrencyScale "SEK" = UnitScale "SEK" "ore"
type CurrencyScale "SGD" Source # 
Instance details
type CurrencyScale "SGD" = UnitScale "SGD" "cent"
type CurrencyScale "SHP" Source # 
Instance details
type CurrencyScale "SHP" = UnitScale "SHP" "penny"
type CurrencyScale "SLL" Source # 
Instance details
type CurrencyScale "SLL" = UnitScale "SLL" "cent"
type CurrencyScale "SOS" Source # 
Instance details
type CurrencyScale "SOS" = UnitScale "SOS" "cent"
type CurrencyScale "SRD" Source # 
Instance details
type CurrencyScale "SRD" = UnitScale "SRD" "cent"
type CurrencyScale "SSP" Source # 
Instance details
type CurrencyScale "SSP" = UnitScale "SSP" "piastre"
type CurrencyScale "STD" Source # 
Instance details
type CurrencyScale "STD" = UnitScale "STD" "centimo"
type CurrencyScale "SVC" Source # 
Instance details
type CurrencyScale "SVC" = UnitScale "SVC" "centavo"
type CurrencyScale "SYP" Source # 
Instance details
type CurrencyScale "SYP" = UnitScale "SYP" "piastre"
type CurrencyScale "SZL" Source # 
Instance details
type CurrencyScale "SZL" = UnitScale "SZL" "cent"
type CurrencyScale "THB" Source # 
Instance details
type CurrencyScale "THB" = UnitScale "THB" "satang"
type CurrencyScale "TJS" Source # 
Instance details
type CurrencyScale "TJS" = UnitScale "TJS" "diram"
type CurrencyScale "TMT" Source # 
Instance details
type CurrencyScale "TMT" = UnitScale "TMT" "tennesi"
type CurrencyScale "TND" Source # 
Instance details
type CurrencyScale "TND" = UnitScale "TND" "millime"
type CurrencyScale "TOP" Source # 
Instance details
type CurrencyScale "TOP" = UnitScale "TOP" "seniti"
type CurrencyScale "TRY" Source # 
Instance details
type CurrencyScale "TRY" = UnitScale "TRY" "kurus"
type CurrencyScale "TTD" Source # 
Instance details
type CurrencyScale "TTD" = UnitScale "TTD" "cent"
type CurrencyScale "TWD" Source # 
Instance details
type CurrencyScale "TWD" = UnitScale "TWD" "cent"
type CurrencyScale "TZS" Source # 
Instance details
type CurrencyScale "TZS" = UnitScale "TZS" "cent"
type CurrencyScale "UAH" Source # 
Instance details
type CurrencyScale "UAH" = UnitScale "UAH" "kopiyka"
type CurrencyScale "UGX" Source # 
Instance details
type CurrencyScale "UGX" = UnitScale "UGX" "cent"
type CurrencyScale "USD" Source # 
Instance details
type CurrencyScale "USD" = UnitScale "USD" "cent"
type CurrencyScale "USN" Source # 
Instance details
type CurrencyScale "USN" = UnitScale "USN" "cent"
type CurrencyScale "UYI" Source # 
Instance details
type CurrencyScale "UYI" = (,) 1 1
type CurrencyScale "UYU" Source # 
Instance details
type CurrencyScale "UYU" = UnitScale "UYU" "centesimo"
type CurrencyScale "UYW" Source # 
Instance details
type CurrencyScale "UYW" = (,) 10000 1
type CurrencyScale "UZS" Source # 
Instance details
type CurrencyScale "UZS" = UnitScale "UZS" "tiyin"
type CurrencyScale "VEF" Source # 
Instance details
type CurrencyScale "VEF" = UnitScale "VEF" "centimo"
type CurrencyScale "VES" Source # 
Instance details
type CurrencyScale "VES" = UnitScale "VES" "centimo"
type CurrencyScale "VND" Source # 
Instance details
type CurrencyScale "VND" = UnitScale "VND" "hao"
type CurrencyScale "VUV" Source # 
Instance details
type CurrencyScale "VUV" = UnitScale "VUV" "vatu"
type CurrencyScale "WST" Source # 
Instance details
type CurrencyScale "WST" = UnitScale "WST" "sene"
type CurrencyScale "XAF" Source # 
Instance details
type CurrencyScale "XAF" = UnitScale "XAF" "centime"
type CurrencyScale "XAG" Source # 
Instance details
type CurrencyScale "XAG" = (ErrScaleNonCanonical "XAU" :: (Nat, Nat))
type CurrencyScale "XAU" Source # 
Instance details
type CurrencyScale "XAU" = (ErrScaleNonCanonical "XAU" :: (Nat, Nat))
type CurrencyScale "XBT" Source # 
Instance details
type CurrencyScale "XBT" = CurrencyScale "BTC"
type CurrencyScale "XCD" Source # 
Instance details
type CurrencyScale "XCD" = UnitScale "XCD" "cent"
type CurrencyScale "XDR" Source # 
Instance details
type CurrencyScale "XDR" = (,) 1 1
type CurrencyScale "XMR" Source # 
Instance details
type CurrencyScale "XMR" = UnitScale "XMR" "piconero"
type CurrencyScale "XOF" Source # 
Instance details
type CurrencyScale "XOF" = UnitScale "XOF" "centime"
type CurrencyScale "XPD" Source # 
Instance details
type CurrencyScale "XPD" = (ErrScaleNonCanonical "XPD" :: (Nat, Nat))
type CurrencyScale "XPF" Source # 
Instance details
type CurrencyScale "XPF" = UnitScale "XPF" "centime"
type CurrencyScale "XPT" Source # 
Instance details
type CurrencyScale "XPT" = (ErrScaleNonCanonical "XPT" :: (Nat, Nat))
type CurrencyScale "XRP" Source # 
Instance details
type CurrencyScale "XRP" = UnitScale "XRP" "drop"
type CurrencyScale "XSU" Source # 
Instance details
type CurrencyScale "XSU" = (,) 1 1
type CurrencyScale "XUA" Source # 
Instance details
type CurrencyScale "XUA" = (,) 1 1
type CurrencyScale "YER" Source # 
Instance details
type CurrencyScale "YER" = UnitScale "YER" "fils"
type CurrencyScale "ZAR" Source # 
Instance details
type CurrencyScale "ZAR" = UnitScale "ZAR" "cent"
type CurrencyScale "ZMW" Source # 
Instance details
type CurrencyScale "ZMW" = UnitScale "ZMW" "ngwee"
type CurrencyScale "ZWL" Source # 
Instance details
type CurrencyScale "ZWL" = UnitScale "ZWL" "cent"

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 UnitScale currency unit) expected to always be satisfied. In particular, the scale is always guaranteed to be a positive rational number (infinity 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.

Equations

ErrScaleNonCanonical c = TypeError ((Text c :<>: Text " is not a currency with a canonical smallest unit,") :$$: Text "be explicit about the currency unit you want to use.") 

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
Category ExchangeRate Source #

Composition of ExchangeRates multiplies exchange rates together:

exchangeRateToRational x * exchangeRateToRational y  ==  exchangeRateToRational (x . y)

Identity:

x  ==  x . id  ==  id . x

Associativity:

x . y . z  ==  x . (y . z)  ==  (x . y) . z

Conmutativity (provided the types allow for composition):

x . y  ==  y . x

Reciprocal:

1  ==  exchangeRateToRational (x . exchangeRateRecip x)
Instance details

Methods

id :: ExchangeRate a a #

(.) :: ExchangeRate b c -> ExchangeRate a b -> ExchangeRate a c #

Eq (ExchangeRate src dst) Source # 
Instance details

Methods

(==) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

(/=) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

Ord (ExchangeRate src dst) Source # 
Instance details

Methods

compare :: ExchangeRate src dst -> ExchangeRate src dst -> Ordering #

(<) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

(<=) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

(>) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

(>=) :: ExchangeRate src dst -> ExchangeRate src dst -> Bool #

max :: ExchangeRate src dst -> ExchangeRate src dst -> ExchangeRate src dst #

min :: ExchangeRate src dst -> ExchangeRate src dst -> ExchangeRate src dst #

(KnownSymbol src, KnownSymbol dst) => Read (ExchangeRate src dst) Source # 
Instance details
(KnownSymbol src, KnownSymbol dst) => Show (ExchangeRate src dst) Source #
> show (exchangeRate (5 % 7) :: Maybe (ExchangeRate "USD" "JPY"))@
Just "ExchangeRate \"USD\" \"JPY\" 5%7"
Instance details

Methods

showsPrec :: Int -> ExchangeRate src dst -> ShowS #

show :: ExchangeRate src dst -> String #

showList :: [ExchangeRate src dst] -> ShowS #

Generic (ExchangeRate src dst) Source # 
Instance details

Associated Types

type Rep (ExchangeRate src dst) :: * -> * #

Methods

from :: ExchangeRate src dst -> Rep (ExchangeRate src dst) x #

to :: Rep (ExchangeRate src dst) x -> ExchangeRate src dst #

Arbitrary (ExchangeRate src dst) Source # 
Instance details

Methods

arbitrary :: Gen (ExchangeRate src dst) #

shrink :: ExchangeRate src dst -> [ExchangeRate src dst] #

(KnownSymbol src, KnownSymbol dst) => Binary (ExchangeRate src dst) Source #

Compatible with SomeExchangeRate.

Instance details

Methods

put :: ExchangeRate src dst -> Put #

get :: Get (ExchangeRate src dst) #

putList :: [ExchangeRate src dst] -> Put #

NFData (ExchangeRate src dst) Source # 
Instance details

Methods

rnf :: ExchangeRate src dst -> () #

Hashable (ExchangeRate src dst) Source # 
Instance details

Methods

hashWithSalt :: Int -> ExchangeRate src dst -> Int #

hash :: ExchangeRate src dst -> Int #

type Rep (ExchangeRate src dst) Source # 
Instance details
type Rep (ExchangeRate src dst) = D1 (MetaData "ExchangeRate" "Money.Internal" "safe-money-0.8.1-inplace" True) (C1 (MetaCons "ExchangeRate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational)))

exchangeRate :: Rational -> Maybe (ExchangeRate src dst) Source #

Safely construct an ExchangeRate from a *positive* Rational number.

If the given Rational is non-positive, returns Nothing.

exchange :: ExchangeRate src dst -> Dense src -> Dense dst Source #

Apply the ExchangeRate to the given Dense src monetary value.

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 #

Arguments

:: DecimalConf

Config to use for parsing the decimal number.

Notice that a leading '-' or '+' will always be correctly interpreted, notwithstanding what the “leading '+'” policy is on the given DecimalConf.

-> Text

The raw string containing the decimal representation (e.g., "1,234.56789").

-> Maybe (ExchangeRate src dst) 

Parses a decimal representation of an ExchangeRate.

exchangeRateToDecimal Source #

Arguments

:: DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the ExchangeRate amount in as many decimal numbers as requested.

-> ExchangeRate src dst

The ExchangeRate to render.

-> 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

data SomeDense Source #

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 # 
Instance details
Ord SomeDense Source #

WARNING This instance does not compare monetary amounts across different currencies, it just helps you sort SomeDense values in case you need to put them in a Set or similar.

Instance details
Show SomeDense Source # 
Instance details
Generic SomeDense Source # 
Instance details

Associated Types

type Rep SomeDense :: * -> * #

Arbitrary SomeDense Source # 
Instance details
Binary SomeDense Source #

Compatible with Dense.

Instance details
NFData SomeDense Source # 
Instance details

Methods

rnf :: SomeDense -> () #

Hashable SomeDense Source # 
Instance details
type Rep SomeDense Source # 
Instance details
type Rep SomeDense = D1 (MetaData "SomeDense" "Money.Internal" "safe-money-0.8.1-inplace" 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 #

Convert a Dense to a SomeDense for ease of serialization.

mkSomeDense Source #

Arguments

:: Text

Currency. (someDenseCurrency)

-> Rational

Amount. (someDenseAmount)

-> Maybe SomeDense 

Build a SomeDense from raw values.

This function is intended for deserialization purposes. You need to convert this SomeDense value to a Dense value in order to do any arithmetic operation on the monetary value.

fromSomeDense Source #

Arguments

:: KnownSymbol currency 
=> SomeDense 
-> Maybe (Dense currency) 

Attempt to convert a SomeDense to a Dense, provided you know the target currency.

withSomeDense Source #

Arguments

:: 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.

someDenseToDecimal Source #

Arguments

:: DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the SomeDense amount in as many decimal numbers as requested.

-> SomeDense

The monetary amount to render.

-> Text 

Like denseToDecimal, but takes a SomeDense as input.

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
Eq SomeDiscrete Source # 
Instance details
Ord SomeDiscrete Source #

WARNING This instance does not compare monetary amounts across different currencies, it just helps you sort SomeDiscrete values in case you need to put them in a Set or similar.

Instance details
Show SomeDiscrete Source # 
Instance details
Generic SomeDiscrete Source # 
Instance details

Associated Types

type Rep SomeDiscrete :: * -> * #

Arbitrary SomeDiscrete Source # 
Instance details
Binary SomeDiscrete Source #

Compatible with Discrete.

Instance details
NFData SomeDiscrete Source # 
Instance details

Methods

rnf :: SomeDiscrete -> () #

Hashable SomeDiscrete Source # 
Instance details
type Rep SomeDiscrete Source # 
Instance details
type Rep SomeDiscrete = D1 (MetaData "SomeDiscrete" "Money.Internal" "safe-money-0.8.1-inplace" False) (C1 (MetaCons "SomeDiscrete" PrefixI True) (S1 (MetaSel (Just "_someDiscreteCurrency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: (S1 (MetaSel (Just "_someDiscreteScale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Scale) :*: S1 (MetaSel (Just "_someDiscreteAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer))))

toSomeDiscrete Source #

Arguments

:: (KnownSymbol currency, GoodScale scale) 
=> Discrete' currency scale 
-> SomeDiscrete 

Convert a Discrete to a SomeDiscrete for ease of serialization.

mkSomeDiscrete Source #

Arguments

:: Text

Currency name. (someDiscreteCurrency)

-> Scale

Scale. Positive, non-zero. (someDiscreteScale)

-> Integer

Amount of unit. (someDiscreteAmount)

-> 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.

fromSomeDiscrete Source #

Arguments

:: (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.

withSomeDiscrete Source #

Arguments

:: 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 #

Arguments

:: DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the SomeDiscrete amount in as many decimal numbers as requested.

-> SomeDiscrete

The monetary amount to render.

-> Text 

Like discreteToDecimal, but takes a SomeDiscrete as input.

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
Eq SomeExchangeRate Source # 
Instance details
Ord SomeExchangeRate Source #

WARNING This instance does not compare rates across different currency pairs (whatever that means), it just helps you sort SomeExchangeRate values in case you need to put them in a Set or similar.

Instance details
Show SomeExchangeRate Source # 
Instance details
Generic SomeExchangeRate Source # 
Instance details

Associated Types

type Rep SomeExchangeRate :: * -> * #

Arbitrary SomeExchangeRate Source # 
Instance details
Binary SomeExchangeRate Source #

Compatible with ExchangeRate.

Instance details
NFData SomeExchangeRate Source # 
Instance details

Methods

rnf :: SomeExchangeRate -> () #

Hashable SomeExchangeRate Source # 
Instance details
type Rep SomeExchangeRate Source # 
Instance details
type Rep SomeExchangeRate = D1 (MetaData "SomeExchangeRate" "Money.Internal" "safe-money-0.8.1-inplace" False) (C1 (MetaCons "SomeExchangeRate" PrefixI True) (S1 (MetaSel (Just "_someExchangeRateSrcCurrency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: (S1 (MetaSel (Just "_someExchangeRateDstCurrency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: S1 (MetaSel (Just "_someExchangeRateRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Rational))))

toSomeExchangeRate Source #

Arguments

:: (KnownSymbol src, KnownSymbol dst) 
=> ExchangeRate src dst 
-> SomeExchangeRate 

Convert a ExchangeRate to a SomeDiscrete for ease of serialization.

mkSomeExchangeRate Source #

Arguments

:: Text

Source currency name. (someExchangeRateSrcCurrency)

-> Text

Destination currency name. (someExchangeRateDstCurrency)

-> Rational

Exchange rate . Positive, non-zero. (someExchangeRateRate)

-> 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.

fromSomeExchangeRate Source #

Arguments

:: (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.

withSomeExchangeRate Source #

Arguments

:: 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 #

Arguments

:: DecimalConf

Config to use for rendering the decimal number.

-> Approximation

Approximation to use if necessary in order to fit the SomeExchangeRate amount in as many decimal numbers as requested.

-> SomeExchangeRate

The SomeExchangeRate to render.

-> Text 

Like exchangeRateToDecimal, but takes a SomeExchangeRate as input.

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.

Constructors

Round

Approximate x to the nearest integer, or to the nearest even integer if x is equidistant between two integers.

Floor

Approximate x to the nearest integer less than or equal to x.

Ceiling

Approximate x to the nearest integer greater than or equal to x.

Truncate

Approximate x to the nearest integer betwen 0 and x, inclusive.

HalfEven

Approximate x to the nearest even integer, when equidistant from the nearest two integers. This is also known as “Bankers Rounding”.

Instances
Eq Approximation Source # 
Instance details
Ord Approximation Source # 
Instance details
Read Approximation Source # 
Instance details
Show Approximation Source # 
Instance details
Generic Approximation Source # 
Instance details

Associated Types

type Rep Approximation :: * -> * #

Arbitrary Approximation Source # 
Instance details
NFData Approximation Source # 
Instance details

Methods

rnf :: Approximation -> () #

Hashable Approximation Source # 
Instance details
type Rep Approximation Source # 
Instance details
type Rep Approximation = D1 (MetaData "Approximation" "Money.Internal" "safe-money-0.8.1-inplace" False) ((C1 (MetaCons "Round" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Floor" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Ceiling" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Truncate" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "HalfEven" PrefixI False) (U1 :: * -> *))))

Decimal config

data DecimalConf Source #

Config to use when rendering or parsing decimal numbers.

See defaultDecimalConf.

Constructors

DecimalConf 

Fields

  • decimalConf_separators :: !Separators

    Decimal and thousands separators to use when rendering the decimal number. Construct one with mkSeparators, or pick a ready made one like separatorsDot or separatorsDotNarrownbsp.

  • decimalConf_leadingPlus :: !Bool

    Whether to render a leading '+' sign in case the amount is positive.

  • decimalConf_digits :: !Word8

    Number of decimal numbers to render, if any.

  • decimalConf_scale :: !Scale

    Scale used to when rendering the decimal number. This is useful if, for example, you want to render a “number of cents” rather than a “number of dollars” as the whole part of the decimal number when rendering a USD amount. It's particularly useful when rendering currencies such as XAU, where one might prefer to render amounts as a number of grams, rather than as a number of troy-ounces.

    Set this to 1 if you don't care.

    For example, when rendering render dense' (123 % 100) :: Dense "USD" as a decimal number with two decimal places, a scale of 1 (analogous to UnitScale "USD" "dollar") would render 1 as the integer part and 23 as the fractional part, whereas a scale of 100 (analogous UnitScale "USD" "cent") would render 123 as the integer part and 00 as the fractional part.

    You can easily obtain the scale for a particular currency and unit combination using the scale function.

    Important: Generally, you will want this number to be 1 or larger. This is because scales in the range (0, 1) can be particularly lossy unless the number of decimal digits is sufficiently large.

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 # 
Instance details
Show Separators Source # 
Instance details
Arbitrary Separators Source # 
Instance details

mkSeparators Source #

Arguments

:: Char

Decimal separator (i.e., the '.' in 1,234.56789)

-> Maybe Char

Thousands separator for the integer part, if any (i.e., the ',' in 1,234.56789).

-> 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.

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').

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').