haspara-0.0.0.0: A library providing definitions to work with monetary values.
Safe HaskellNone
LanguageHaskell2010

Haspara.Money

Description

This module provides base data definitions and functions for Haspara library.

Synopsis

Money

Data Definition

data Money (s :: Nat) Source #

Instances

Instances details
Eq (Money s) Source # 
Instance details

Defined in Haspara.Internal.Money

Methods

(==) :: Money s -> Money s -> Bool #

(/=) :: Money s -> Money s -> Bool #

Ord (Money s) Source # 
Instance details

Defined in Haspara.Internal.Money

Methods

compare :: 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 #

max :: Money s -> Money s -> Money s #

min :: Money s -> Money s -> Money s #

KnownNat s => Show (Money s) Source # 
Instance details

Defined in Haspara.Internal.Money

Methods

showsPrec :: Int -> Money s -> ShowS #

show :: Money s -> String #

showList :: [Money s] -> ShowS #

KnownNat s => ToJSON (Money s) Source #

ToJSON instance for Money.

>>> Aeson.encode (MoneySome (read "2021-01-01") ("USD" :: Currency) (42 :: Quantity 0))
"{\"qty\":42,\"ccy\":\"USD\",\"date\":\"2021-01-01\"}"
>>> Aeson.encode (MoneyZero :: Money 2)
"0"
>>> Aeson.encode (MoneyFail "oops" :: Money 2)
"{\"error\":\"oops\"}"
Instance details

Defined in Haspara.Internal.Money

KnownNat s => FromJSON (Money s) Source #

FromJSON instance for Money.

>>> Aeson.decode "{\"qty\":42,\"ccy\":\"USD\",\"date\":\"2021-01-01\"}" :: Maybe (Money 2)
Just (MoneySome 2021-01-01 USD 42.00)
>>> Aeson.decode "0" :: Maybe (Money 2)
Just MoneyZero
>>> Aeson.decode "{\"error\": \"oops\"}" :: Maybe (Money 2)
Just (MoneyFail "oops")
Instance details

Defined in Haspara.Internal.Money

Constructors

Operations

convert :: (KnownNat s, KnownNat k) => Money s -> Currency -> Quantity k -> Money s Source #

Converts the given Money value to another given currency with the given rate.

>>> import Haspara
>>> let eur = either error id $ currency "EUR"
>>> let usd = either error id $ currency "USD"
>>> let date = read "2021-01-01" :: Date
>>> let eurmoney = mkMoney date eur (quantity 0.42 :: Quantity 2) :: Money 2
>>> convert eurmoney eur (quantity 1 :: Quantity 4)
MoneySome 2021-01-01 EUR 0.42
>>> convert eurmoney usd (quantity 1 :: Quantity 4)
MoneySome 2021-01-01 USD 0.42
>>> convert eurmoney usd (quantity 1.1516 :: Quantity 4)
MoneySome 2021-01-01 USD 0.48

convertWithQuote :: (KnownNat s, KnownNat k) => Money s -> FXQuote k -> Money s Source #

Converts the given Money value to another currency with the given FXQuote.