Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides internal definitions for modeling and working with currencies.
Synopsis
- newtype Currency = MkCurrency {
- currencyCode :: Text
- currency :: MonadError String m => Text -> m Currency
- currencyFail :: MonadFail m => Text -> m Currency
- currencyCodeParser :: Parsec Void Text Text
- newtype CurrencyPair = MkCurrencyPair {
- unCurrencyPair :: (Currency, Currency)
- toTuple :: CurrencyPair -> (Currency, Currency)
- baseCurrency :: CurrencyPair -> Currency
- quoteCurrency :: CurrencyPair -> Currency
- currencyPair :: MonadError String m => Currency -> Currency -> m CurrencyPair
- currencyPairFail :: MonadFail m => Currency -> Currency -> m CurrencyPair
Data Definition
Type encoding for currencies.
Instances
Eq Currency Source # | |
Ord Currency Source # | |
Defined in Haspara.Internal.Currency | |
Show Currency Source # |
|
IsString Currency Source # |
|
Defined in Haspara.Internal.Currency fromString :: String -> Currency # | |
Hashable Currency Source # | |
Defined in Haspara.Internal.Currency | |
ToJSON Currency Source # |
|
Defined in Haspara.Internal.Currency | |
FromJSON Currency Source # |
|
Lift Currency Source # | |
Constructors
currency :: MonadError String m => Text -> m Currency Source #
Smart constructor for Currency
values within MonadError
context.
>>>
currency "" :: Either String Currency
Left "Currency code error! Expecting at least 3 uppercase characters, but received: \"\"">>>
currency " " :: Either String Currency
Left "Currency code error! Expecting at least 3 uppercase characters, but received: \" \"">>>
currency "AB" :: Either String Currency
Left "Currency code error! Expecting at least 3 uppercase characters, but received: \"AB\"">>>
currency " ABC " :: Either String Currency
Left "Currency code error! Expecting at least 3 uppercase characters, but received: \" ABC \"">>>
currency "ABC" :: Either String Currency
Right ABC
Auxiliaries
currencyCodeParser :: Parsec Void Text Text Source #
Parser that parses currency codes.
>>>
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"
newtype CurrencyPair Source #
Instances
baseCurrency :: CurrencyPair -> Currency Source #
quoteCurrency :: CurrencyPair -> Currency Source #
currencyPair :: MonadError String m => Currency -> Currency -> m CurrencyPair Source #
currencyPairFail :: MonadFail m => Currency -> Currency -> m CurrencyPair Source #