{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingVia #-}
module Haspara.Monetary where
import Control.Exception (Exception)
import Control.Monad (when)
import Control.Monad.Catch (MonadThrow(throwM))
import Data.Time (Day)
import qualified Deriving.Aeson.Stock as DAS
import GHC.Stack (HasCallStack)
import GHC.TypeLits (KnownNat, Nat)
import Haspara.Currency (Currency, CurrencyPair(..))
import Haspara.FxQuote (FxQuote(..))
import Haspara.Quantity (Quantity, times)
import Refined (unrefine)
data Money (s :: Nat) = Money
{ Money s -> Day
moneyDate :: !Day
, Money s -> Currency
moneyCurrency :: !Currency
, Money s -> Quantity s
moneyQuantity :: !(Quantity s)
}
deriving (Money s -> Money s -> Bool
(Money s -> Money s -> Bool)
-> (Money s -> Money s -> Bool) -> Eq (Money s)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: Nat). Money s -> Money s -> Bool
/= :: Money s -> Money s -> Bool
$c/= :: forall (s :: Nat). Money s -> Money s -> Bool
== :: Money s -> Money s -> Bool
$c== :: forall (s :: Nat). Money s -> Money s -> Bool
Eq, (forall x. Money s -> Rep (Money s) x)
-> (forall x. Rep (Money s) x -> Money s) -> Generic (Money s)
forall x. Rep (Money s) x -> Money s
forall x. Money s -> Rep (Money s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: Nat) x. Rep (Money s) x -> Money s
forall (s :: Nat) x. Money s -> Rep (Money s) x
$cto :: forall (s :: Nat) x. Rep (Money s) x -> Money s
$cfrom :: forall (s :: Nat) x. Money s -> Rep (Money s) x
DAS.Generic, Eq (Money s)
Eq (Money s)
-> (Money s -> Money s -> Ordering)
-> (Money s -> Money s -> Bool)
-> (Money s -> Money s -> Bool)
-> (Money s -> Money s -> Bool)
-> (Money s -> Money s -> Bool)
-> (Money s -> Money s -> Money s)
-> (Money s -> Money s -> Money s)
-> Ord (Money s)
Money s -> Money s -> Bool
Money s -> Money s -> Ordering
Money s -> Money s -> Money s
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (s :: Nat). Eq (Money s)
forall (s :: Nat). Money s -> Money s -> Bool
forall (s :: Nat). Money s -> Money s -> Ordering
forall (s :: Nat). Money s -> Money s -> Money s
min :: Money s -> Money s -> Money s
$cmin :: forall (s :: Nat). Money s -> Money s -> Money s
max :: Money s -> Money s -> Money s
$cmax :: forall (s :: Nat). Money s -> Money s -> Money s
>= :: Money s -> Money s -> Bool
$c>= :: forall (s :: Nat). Money s -> Money s -> Bool
> :: Money s -> Money s -> Bool
$c> :: forall (s :: Nat). Money s -> Money s -> Bool
<= :: Money s -> Money s -> Bool
$c<= :: forall (s :: Nat). Money s -> Money s -> Bool
< :: Money s -> Money s -> Bool
$c< :: forall (s :: Nat). Money s -> Money s -> Bool
compare :: Money s -> Money s -> Ordering
$ccompare :: forall (s :: Nat). Money s -> Money s -> Ordering
$cp1Ord :: forall (s :: Nat). Eq (Money s)
Ord, Int -> Money s -> ShowS
[Money s] -> ShowS
Money s -> String
(Int -> Money s -> ShowS)
-> (Money s -> String) -> ([Money s] -> ShowS) -> Show (Money s)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (s :: Nat). KnownNat s => Int -> Money s -> ShowS
forall (s :: Nat). KnownNat s => [Money s] -> ShowS
forall (s :: Nat). KnownNat s => Money s -> String
showList :: [Money s] -> ShowS
$cshowList :: forall (s :: Nat). KnownNat s => [Money s] -> ShowS
show :: Money s -> String
$cshow :: forall (s :: Nat). KnownNat s => Money s -> String
showsPrec :: Int -> Money s -> ShowS
$cshowsPrec :: forall (s :: Nat). KnownNat s => Int -> Money s -> ShowS
Show)
deriving (Value -> Parser [Money s]
Value -> Parser (Money s)
(Value -> Parser (Money s))
-> (Value -> Parser [Money s]) -> FromJSON (Money s)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
forall (s :: Nat). KnownNat s => Value -> Parser [Money s]
forall (s :: Nat). KnownNat s => Value -> Parser (Money s)
parseJSONList :: Value -> Parser [Money s]
$cparseJSONList :: forall (s :: Nat). KnownNat s => Value -> Parser [Money s]
parseJSON :: Value -> Parser (Money s)
$cparseJSON :: forall (s :: Nat). KnownNat s => Value -> Parser (Money s)
DAS.FromJSON, [Money s] -> Encoding
[Money s] -> Value
Money s -> Encoding
Money s -> Value
(Money s -> Value)
-> (Money s -> Encoding)
-> ([Money s] -> Value)
-> ([Money s] -> Encoding)
-> ToJSON (Money s)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
forall (s :: Nat). KnownNat s => [Money s] -> Encoding
forall (s :: Nat). KnownNat s => [Money s] -> Value
forall (s :: Nat). KnownNat s => Money s -> Encoding
forall (s :: Nat). KnownNat s => Money s -> Value
toEncodingList :: [Money s] -> Encoding
$ctoEncodingList :: forall (s :: Nat). KnownNat s => [Money s] -> Encoding
toJSONList :: [Money s] -> Value
$ctoJSONList :: forall (s :: Nat). KnownNat s => [Money s] -> Value
toEncoding :: Money s -> Encoding
$ctoEncoding :: forall (s :: Nat). KnownNat s => Money s -> Encoding
toJSON :: Money s -> Value
$ctoJSON :: forall (s :: Nat). KnownNat s => Money s -> Value
DAS.ToJSON) via DAS.PrefixedSnake "money" (Money s)
class MonadThrow m => Monetary m where
convertM
:: HasCallStack
=> KnownNat s
=> Currency
-> Money s
-> m (Money s)
convertAsofM
:: HasCallStack
=> KnownNat s
=> Day
-> Currency
-> Money s
-> m (Money s)
convertAsofM Day
date Currency
ccyN (Money Day
_ Currency
ccy Quantity s
qty) = Currency -> Money s -> m (Money s)
forall (m :: * -> *) (s :: Nat).
(Monetary m, HasCallStack, KnownNat s) =>
Currency -> Money s -> m (Money s)
convertM Currency
ccyN (Day -> Currency -> Quantity s -> Money s
forall (s :: Nat). Day -> Currency -> Quantity s -> Money s
Money Day
date Currency
ccy Quantity s
qty)
convert
:: HasCallStack
=> MonadThrow m
=> KnownNat s
=> KnownNat k
=> Money s
-> FxQuote k
-> m (Money s)
convert :: Money s -> FxQuote k -> m (Money s)
convert (Money Day
date Currency
ccy Quantity s
qty) quote :: FxQuote k
quote@(MkFxQuote (CurrencyPair Currency
ccy1 Currency
ccy2) Day
asof Refined Positive (Quantity k)
rate) = do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Currency
ccy Currency -> Currency -> Bool
forall a. Eq a => a -> a -> Bool
/= Currency
ccy1) (MonetaryException -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (HasCallStack => Currency -> Currency -> MonetaryException
Currency -> Currency -> MonetaryException
IncompatibleCurrenciesException Currency
ccy Currency
ccy1))
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Day
asof Day -> Day -> Bool
forall a. Ord a => a -> a -> Bool
< Day
date) (MonetaryException -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (HasCallStack => Day -> Day -> MonetaryException
Day -> Day -> MonetaryException
IncompatibleDatesException Day
date Day
asof))
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Currency
ccy1 Currency -> Currency -> Bool
forall a. Eq a => a -> a -> Bool
== Currency
ccy2 Bool -> Bool -> Bool
&& Refined Positive (Quantity k) -> Quantity k
forall p x. Refined p x -> x
unrefine Refined Positive (Quantity k)
rate Quantity k -> Quantity k -> Bool
forall a. Eq a => a -> a -> Bool
/= Quantity k
1) (MonetaryException -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FxQuote k -> MonetaryException
forall (s :: Nat).
(HasCallStack, KnownNat s) =>
FxQuote s -> MonetaryException
InconsistentFxQuoteException FxQuote k
quote))
Money s -> m (Money s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Day -> Currency -> Quantity s -> Money s
forall (s :: Nat). Day -> Currency -> Quantity s -> Money s
Money Day
asof Currency
ccy2 (Quantity s -> Quantity k -> Quantity s
forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
times Quantity s
qty (Refined Positive (Quantity k) -> Quantity k
forall p x. Refined p x -> x
unrefine Refined Positive (Quantity k)
rate)))
data MonetaryException where
IncompatibleCurrenciesException
:: HasCallStack
=> Currency
-> Currency
-> MonetaryException
IncompatibleDatesException
:: HasCallStack
=> Day
-> Day
-> MonetaryException
InconsistentFxQuoteException
:: forall (s :: Nat). (HasCallStack, KnownNat s)
=> FxQuote s
-> MonetaryException
deriving instance Show MonetaryException
instance Exception MonetaryException