Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides definitions for modeling and working with foreign exchange (FX) rate quotations.
Synopsis
- data FxQuote (s :: Nat) = MkFxQuote {
- fxQuotePair :: !CurrencyPair
- fxQuoteDate :: !Day
- fxQuoteRate :: !(Refined Positive (Quantity s))
- mkFxQuoteError :: MonadError Text m => KnownNat s => Currency -> Currency -> Day -> Scientific -> m (FxQuote s)
- mkFxQuoteFail :: MonadFail m => KnownNat s => Currency -> Currency -> Day -> Scientific -> m (FxQuote s)
- mkFxQuoteUnsafe :: KnownNat s => Currency -> Currency -> Day -> Scientific -> FxQuote s
- type FxQuoteDatabase (n :: Nat) = Map CurrencyPair (FxQuotePairDatabase n)
- data FxQuotePairDatabase (n :: Nat) = FxQuotePairDatabase {}
- findFxQuote :: KnownNat n => FxQuoteDatabase n -> CurrencyPair -> Day -> Maybe (FxQuote n)
- findFxQuoteAux :: KnownNat n => Day -> FxQuotePairDatabase n -> Maybe (FxQuote n)
- emptyFxQuoteDatabase :: KnownNat n => FxQuoteDatabase n
- addFxQuotes :: KnownNat n => [FxQuote n] -> FxQuoteDatabase n -> FxQuoteDatabase n
- addFxQuote :: KnownNat n => FxQuote n -> FxQuoteDatabase n -> FxQuoteDatabase n
- initFxQuotePairDatabase :: KnownNat n => FxQuote n -> FxQuotePairDatabase n
- updateFxQuotePairDatabase :: KnownNat n => FxQuote n -> FxQuotePairDatabase n -> FxQuotePairDatabase n
FX Rate Quotation
data FxQuote (s :: Nat) Source #
Type encoding for FX rate quotations with fixed precision.
An FX rate quotation is a 3-tuple of:
- a currency pair the rate is quoted for, and
- a date that the quotation is effective as of,
- a (positive) rate as the value of the quotation.
MkFxQuote | |
|
Instances
Eq (FxQuote s) Source # | |
Ord (FxQuote s) Source # | |
Defined in Haspara.FxQuote | |
KnownNat s => Show (FxQuote s) Source # | |
Generic (FxQuote s) Source # | |
KnownNat s => ToJSON (FxQuote s) Source # | |
Defined in Haspara.FxQuote | |
KnownNat s => FromJSON (FxQuote s) Source # | |
type Rep (FxQuote s) Source # | |
Defined in Haspara.FxQuote type Rep (FxQuote s) = D1 ('MetaData "FxQuote" "Haspara.FxQuote" "haspara-0.0.0.4-91kyQ1gsJrx6JOOKY5ajCi" 'False) (C1 ('MetaCons "MkFxQuote" 'PrefixI 'True) (S1 ('MetaSel ('Just "fxQuotePair") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CurrencyPair) :*: (S1 ('MetaSel ('Just "fxQuoteDate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Just "fxQuoteRate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Refined Positive (Quantity s)))))) |
:: MonadError Text m | |
=> KnownNat s | |
=> Currency | Base currency (from) of the FX quotation. |
-> Currency | Quote currency (to) of the FX quotation. |
-> Day | Date of the FX quotation. |
-> Scientific | FX quotation rate, expected to be positive. |
-> m (FxQuote s) |
Smart constructor for FxQuote
values within
context.MonadError
Text
The rate is expected to be a positive value. If it is not, the function will throw an error.
>>>
mkFxQuoteError @(Either _) @2 "EUR" "USD" (read "2021-12-31") 1.16
Right (MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 1.16})>>>
mkFxQuoteError @(Either _) @2 "EUR" "USD" (read "2021-12-31") (-1.16)
Left "Can not create FX Rate. Error was: The predicate (GreaterThan 0) failed with the message: Value is not greater than 0\n"
:: MonadFail m | |
=> KnownNat s | |
=> Currency | Base currency (from) of the FX quotation. |
-> Currency | Quote currency (to) of the FX quotation. |
-> Day | Date of the FX quotation. |
-> Scientific | FX quotation rate, expected to be positive. |
-> m (FxQuote s) |
Smart constructor for FxQuote
values within MonadFail
context.
The rate is expected to be a positive value. If it is not, the function will
fail.
>>> mkFxQuoteFail Maybe
2 EUR USD (read "2021-12-31") 1.16
Just (MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 1.16})
>>> mkFxQuoteFail Maybe
2 EUR USD (read "2021-12-31") (-1.16)
Nothing
:: KnownNat s | |
=> Currency | Base currency (from) of the FX quotation. |
-> Currency | Quote currency (to) of the FX quotation. |
-> Day | Date of the FX quotation. |
-> Scientific | FX quotation rate, expected to be positive. |
-> FxQuote s |
Unsafe FxQuote
constructor that error
s if it fails.
>>>
mkFxQuoteUnsafe @2 "EUR" "USD" (read "2021-12-31") 1.16
MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 1.16}>>>
mkFxQuoteUnsafe @2 "EUR" "USD" (read "2021-12-31") (-1.16)
... ...Can not create FX Rate. Error was: The predicate (GreaterThan 0) failed with the message: Value is not greater than 0 ...
FX Rate Quotation Database
>>>
let database = addFxQuotes [mkFxQuoteUnsafe @8 "EUR" "USD" (read "2021-12-31") 1.13, mkFxQuoteUnsafe @8 "EUR" "TRY" (read "2021-12-31") 15.14] emptyFxQuoteDatabase
>>>
findFxQuote database (CurrencyPair "EUR" "USD") (read "2021-12-31")
Just (MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 1.13000000})>>>
findFxQuote database (CurrencyPair "EUR" "TRY") (read "2021-12-31")
Just (MkFxQuote {fxQuotePair = EUR/TRY, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 15.14000000})>>>
findFxQuote database (CurrencyPair "EUR" "TRY") (read "2021-12-30")
Nothing>>>
findFxQuote database (CurrencyPair "EUR" "TRY") (read "2022-01-01")
Just (MkFxQuote {fxQuotePair = EUR/TRY, fxQuoteDate = 2021-12-31, fxQuoteRate = Refined 15.14000000})
type FxQuoteDatabase (n :: Nat) = Map CurrencyPair (FxQuotePairDatabase n) Source #
Type encoding for a dictionary-based FX rate quotation database for various
CurrencyPair
values.
data FxQuotePairDatabase (n :: Nat) Source #
Type encoding for FX rate quotation database for a CurrencyPair
.
Instances
KnownNat n => Show (FxQuotePairDatabase n) Source # | |
Defined in Haspara.FxQuote showsPrec :: Int -> FxQuotePairDatabase n -> ShowS # show :: FxQuotePairDatabase n -> String # showList :: [FxQuotePairDatabase n] -> ShowS # |
:: KnownNat n | |
=> FxQuoteDatabase n | FX quotation database to perform the lookup on. |
-> CurrencyPair | Currency pair we are looking for the quotation for. |
-> Day | Date the quotation we look for is valid as of. |
-> Maybe (FxQuote n) |
Attempts to find and return the FX quotation for a given CurrencyPair
as
of a give Day
in a given FxQuoteDatabase
.
findFxQuoteAux :: KnownNat n => Day -> FxQuotePairDatabase n -> Maybe (FxQuote n) Source #
Attempts to find and return the FX quotation as of a give Day
in a given
FxQuotePairDatabase
.
emptyFxQuoteDatabase :: KnownNat n => FxQuoteDatabase n Source #
Returns empty FX rate quotation database.
>>>
emptyFxQuoteDatabase @8
fromList []
addFxQuotes :: KnownNat n => [FxQuote n] -> FxQuoteDatabase n -> FxQuoteDatabase n Source #
Adds a list of FX rate quotations to the given database.
>>>
let database = emptyFxQuoteDatabase @8
>>>
addFxQuotes [] database
fromList []>>>
addFxQuotes [mkFxQuoteUnsafe @8 "EUR" "USD" (read "2021-01-31") 1.13] database
fromList [(EUR/USD,FxQuotePairDatabase {fxQuotePairDatabasePair = EUR/USD, fxQuotePairDatabaseTable = fromList [(2021-01-31,MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-01-31, fxQuoteRate = Refined 1.13000000})], fxQuotePairDatabaseSince = 2021-01-31, fxQuotePairDatabaseUntil = 2021-01-31})]>>>
addFxQuotes [mkFxQuoteUnsafe @8 "EUR" "USD" (read "2021-01-31") 1.13, mkFxQuoteUnsafe @8 "USD" "EUR" (read "2021-01-31") 0.884956] database
fromList [(EUR/USD,FxQuotePairDatabase {fxQuotePairDatabasePair = EUR/USD, fxQuotePairDatabaseTable = fromList [(2021-01-31,MkFxQuote {fxQuotePair = EUR/USD, fxQuoteDate = 2021-01-31, fxQuoteRate = Refined 1.13000000})], fxQuotePairDatabaseSince = 2021-01-31, fxQuotePairDatabaseUntil = 2021-01-31}),(USD/EUR,FxQuotePairDatabase {fxQuotePairDatabasePair = USD/EUR, fxQuotePairDatabaseTable = fromList [(2021-01-31,MkFxQuote {fxQuotePair = USD/EUR, fxQuoteDate = 2021-01-31, fxQuoteRate = Refined 0.88495600})], fxQuotePairDatabaseSince = 2021-01-31, fxQuotePairDatabaseUntil = 2021-01-31})]
addFxQuote :: KnownNat n => FxQuote n -> FxQuoteDatabase n -> FxQuoteDatabase n Source #
Adds an FX rate quotation to the given database.
Internal
initFxQuotePairDatabase :: KnownNat n => FxQuote n -> FxQuotePairDatabase n Source #
Initializes FX quote pair database with the given FX quote.
updateFxQuotePairDatabase :: KnownNat n => FxQuote n -> FxQuotePairDatabase n -> FxQuotePairDatabase n Source #
Updates an existing FX quote pair database with the given FX quote.