module Data.Money
(
USD(..)
, RUB(..)
, EUR(..)
, BTC(..)
, LTC(..)
, CurrencySymbol(..)
, ScalableAdditive(..)
, ExchangeRates
, makeExchangeRates
, Money
, makeMoney
, makeUSD
, makeRUB
, makeEUR
, makeBTC
, makeLTC
, amount
, symbol
, findRate
, exchangeTo
, sampleRates
) where
import qualified Data.Map.Strict as M
import Data.Typeable (Typeable, TypeRep, typeOf)
class (Typeable a, Eq a) => CurrencySymbol a
data USD = USD deriving (Read, Show, Typeable, Eq)
data RUB = RUB deriving (Read, Show, Typeable, Eq)
data EUR = EUR deriving (Read, Show, Typeable, Eq)
data BTC = BTC deriving (Read, Show, Typeable, Eq)
data LTC = LTC deriving (Read, Show, Typeable, Eq)
instance CurrencySymbol USD
instance CurrencySymbol RUB
instance CurrencySymbol EUR
instance CurrencySymbol BTC
instance CurrencySymbol LTC
data Money a = Money
{ amount :: Double
, symbol :: a
} deriving (Read, Show, Eq)
class ScalableAdditive a where
(^*) :: a -> Double -> a
(^+^) :: a -> a -> a
(^-^) :: a -> a -> a
(^/) :: a -> Double -> a
i ^/ c = i ^* (1/c)
instance ScalableAdditive (Money a) where
(^*) (Money a sy) c = Money (c * a) sy
(^+^) (Money a1 sy) (Money a2 _) = Money (a1 + a2) sy
(^-^) (Money a1 sy) (Money a2 _) = Money (a1 a2) sy
makeMoney :: (CurrencySymbol a) => Double -> a -> Money a
makeMoney = Money
makeUSD = flip makeMoney USD
makeRUB = flip makeMoney RUB
makeEUR = flip makeMoney EUR
makeBTC = flip makeMoney BTC
makeLTC = flip makeMoney LTC
data ExchangeRates = ExchangeRates (M.Map (TypeRep, TypeRep) Double)
deriving (Show)
findDirectRate :: (CurrencySymbol a, CurrencySymbol b) => ExchangeRates -> a -> b -> Maybe Double
findDirectRate (ExchangeRates ex) fc tc
| typeOf fc == typeOf tc = Just 1
| otherwise = (M.lookup (typeOf fc, typeOf tc) ex)
findRate :: (CurrencySymbol a, CurrencySymbol b) => ExchangeRates -> a -> b -> Maybe Double
findRate ex fc tc = case findDirectRate ex fc tc of
Nothing -> (/) <$> Just 1 <*> findDirectRate ex tc fc
dr -> dr
exchangeTo :: (CurrencySymbol a, CurrencySymbol b) => ExchangeRates -> Money a -> b -> Maybe (Money b)
exchangeTo ex m sy = do
r <- findRate ex (symbol m) sy
let a = (amount m) * r
return $ Money a sy
makeExchangeRates :: [((TypeRep, TypeRep), Double)] -> ExchangeRates
makeExchangeRates rs = ExchangeRates $ M.fromList rs
sampleRates :: ExchangeRates
sampleRates = ExchangeRates $ M.fromList
[ ((typeOf USD, typeOf RUB), 59.24)
, ((typeOf BTC, typeOf USD), 866.689)
, ((typeOf LTC, typeOf USD), 3.846)
, ((typeOf EUR, typeOf RUB), 63.27)
, ((typeOf EUR, typeOf USD), 1.064)
, ((typeOf BTC, typeOf RUB), 50951.4)
, ((typeOf LTC, typeOf RUB), 225.88)
, ((typeOf LTC, typeOf BTC), 0.00443)
]