Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides definitions for modeling and working with currencies.
Synopsis
- newtype Currency = MkCurrency {
- currencyCode :: Text
- mkCurrencyError :: MonadError Text m => Text -> m Currency
- mkCurrencyFail :: MonadFail m => Text -> m Currency
- currencyCodeParser :: Parsec Void Text Text
- data CurrencyPair = CurrencyPair {}
- toCurrencyTuple :: CurrencyPair -> (Currency, Currency)
- fromCurrencyTuple :: (Currency, Currency) -> CurrencyPair
Currency
Type encoding for currency symbol values with a syntax of [A-Z]{3}[A-Z]*
.
Currency
values can be constructed via mkCurrencyError
that works in
context:MonadError
Text
>>>
:set -XOverloadedStrings
>>>
mkCurrencyError "EUR" :: Either T.Text Currency
Right EUR
... or via mkCurrencyFail
that works in MonadFail
context:
>>>
mkCurrencyFail "EUR" :: Maybe Currency
Just EUR
An IsString
instance is provided as well which is unsafe but convenient:
>>>
"EUR" :: Currency
EUR
Instances
FromJSON Currency Source # |
|
ToJSON Currency Source # |
|
Defined in Haspara.Currency | |
IsString Currency Source # |
|
Defined in Haspara.Currency fromString :: String -> Currency # | |
Show Currency Source # |
|
Eq Currency Source # | |
Ord Currency Source # | |
Defined in Haspara.Currency | |
Hashable Currency Source # | |
Defined in Haspara.Currency | |
Lift Currency Source # | |
mkCurrencyError :: MonadError Text m => Text -> m Currency Source #
Smart constructor for Currency
values within MonadError
context.
>>>
:set -XOverloadedStrings
>>>
mkCurrencyError "" :: Either T.Text Currency
Left "Currency code error! Expecting at least 3 uppercase ASCII letters, but received: ">>>
mkCurrencyError " " :: Either T.Text Currency
Left "Currency code error! Expecting at least 3 uppercase ASCII letters, but received: ">>>
mkCurrencyError "AB" :: Either T.Text Currency
Left "Currency code error! Expecting at least 3 uppercase ASCII letters, but received: AB">>>
mkCurrencyError " ABC " :: Either T.Text Currency
Left "Currency code error! Expecting at least 3 uppercase ASCII letters, but received: ABC ">>>
mkCurrencyError "ABC" :: Either T.Text Currency
Right ABC
currencyCodeParser :: Parsec Void Text Text Source #
Parser that parses currency codes.
>>>
:set -XOverloadedStrings
>>>
MP.runParser currencyCodeParser "Example" ""
Left (ParseErrorBundle {bundleErrors = TrivialError 0 (Just EndOfInput) (fromList []) :| [], bundlePosState = PosState {pstateInput = "", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})>>>
MP.runParser currencyCodeParser "Example" " "
Left (ParseErrorBundle {bundleErrors = TrivialError 0 (Just (Tokens (' ' :| ""))) (fromList []) :| [], bundlePosState = PosState {pstateInput = " ", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})>>>
MP.runParser currencyCodeParser "Example" "a"
Left (ParseErrorBundle {bundleErrors = TrivialError 0 (Just (Tokens ('a' :| ""))) (fromList []) :| [], bundlePosState = PosState {pstateInput = "a", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})>>>
MP.runParser currencyCodeParser "Example" "A"
Left (ParseErrorBundle {bundleErrors = TrivialError 1 (Just EndOfInput) (fromList []) :| [], bundlePosState = PosState {pstateInput = "A", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})>>>
MP.runParser currencyCodeParser "Example" "AB"
Left (ParseErrorBundle {bundleErrors = TrivialError 2 (Just EndOfInput) (fromList []) :| [], bundlePosState = PosState {pstateInput = "AB", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})>>>
MP.runParser currencyCodeParser "Example" "ABC"
Right "ABC">>>
MP.runParser currencyCodeParser "Example" "ABCD"
Right "ABCD">>>
MP.runParser currencyCodeParser "Example" " ABCD "
Left (ParseErrorBundle {bundleErrors = TrivialError 0 (Just (Tokens (' ' :| ""))) (fromList []) :| [], bundlePosState = PosState {pstateInput = " ABCD ", pstateOffset = 0, pstateSourcePos = SourcePos {sourceName = "Example", sourceLine = Pos 1, sourceColumn = Pos 1}, pstateTabWidth = Pos 8, pstateLinePrefix = ""}})
Currency Pair
data CurrencyPair Source #
Type encoding of a currency pair.
CurrencyPair
values are constructed via the data constructor:
>>>
:set -XOverloadedStrings
>>>
CurrencyPair "EUR" "USD"
EUR/USD
FromJSON
and ToJSON
instances are provided as well:
>>>
Aeson.decode "{\"base\": \"EUR\", \"quote\": \"EUR\"}" :: Maybe CurrencyPair
Just EUR/EUR>>>
Aeson.encode (CurrencyPair "EUR" "USD")
"{\"base\":\"EUR\",\"quote\":\"USD\"}"
CurrencyPair | |
|
Instances
toCurrencyTuple :: CurrencyPair -> (Currency, Currency) Source #
Converts a CurrencyPair
to a 2-tuple of Currency
values.
>>>
:set -XOverloadedStrings
>>>
toCurrencyTuple (CurrencyPair "EUR" "USD")
(EUR,USD)
fromCurrencyTuple :: (Currency, Currency) -> CurrencyPair Source #
Converts a 2-tuple of Currency
values to a CurrencyPair
.
>>>
:set -XOverloadedStrings
>>>
fromCurrencyTuple ("EUR", "USD")
EUR/USD