haspara-0.0.0.8: A library providing definitions to work with monetary values.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haspara.Accounting.Amount

Description

This module provides definitions for amounts used as in accounting.

For balance definition that allows "Negative Balance" phenomenon, see Balance.

Synopsis

Documentation

data Amount (precision :: Nat) Source #

Data definition for amounts.

Constructors

Amount 

Fields

Instances

Instances details
KnownNat precision => FromJSON (Amount precision) Source #

FromJSON instance for Amount.

>>> :set -XDataKinds
>>> :set -XOverloadedStrings
>>> Aeson.eitherDecode "{\"side\": \"db\", \"value\": 42}" :: Either String (Amount 2)
Right (Amount {amountSide = SideDebit, amountValue = Refined 42.00})
>>> Aeson.eitherDecode "{\"side\": \"cr\", \"value\": 42}" :: Either String (Amount 2)
Right (Amount {amountSide = SideCredit, amountValue = Refined 42.00})
Instance details

Defined in Haspara.Accounting.Amount

Methods

parseJSON :: Value -> Parser (Amount precision) #

parseJSONList :: Value -> Parser [Amount precision] #

KnownNat precision => ToJSON (Amount precision) Source #

ToJSON instance for Amount.

>>> :set -XDataKinds
>>> import Haspara.Accounting.Side
>>> import Haspara.Quantity
>>> import Refined.Unsafe
>>> Aeson.encode (Amount SideDebit (unsafeRefine (mkQuantity 42 :: Quantity 2)))
"{\"side\":\"db\",\"value\":42.0}"
>>> Aeson.encode (Amount SideCredit (unsafeRefine (mkQuantity 42 :: Quantity 2)))
"{\"side\":\"cr\",\"value\":42.0}"
>>> Aeson.eitherDecode (Aeson.encode (Amount SideDebit (unsafeRefine (mkQuantity 42 :: Quantity 2)))) :: Either String (Amount 2)
Right (Amount {amountSide = SideDebit, amountValue = Refined 42.00})
>>> Aeson.eitherDecode (Aeson.encode (Amount SideCredit (unsafeRefine (mkQuantity 42 :: Quantity 2)))) :: Either String (Amount 2)
Right (Amount {amountSide = SideCredit, amountValue = Refined 42.00})
Instance details

Defined in Haspara.Accounting.Amount

Methods

toJSON :: Amount precision -> Value #

toEncoding :: Amount precision -> Encoding #

toJSONList :: [Amount precision] -> Value #

toEncodingList :: [Amount precision] -> Encoding #

Generic (Amount precision) Source # 
Instance details

Defined in Haspara.Accounting.Amount

Associated Types

type Rep (Amount precision) :: Type -> Type #

Methods

from :: Amount precision -> Rep (Amount precision) x #

to :: Rep (Amount precision) x -> Amount precision #

KnownNat precision => Show (Amount precision) Source # 
Instance details

Defined in Haspara.Accounting.Amount

Methods

showsPrec :: Int -> Amount precision -> ShowS #

show :: Amount precision -> String #

showList :: [Amount precision] -> ShowS #

Eq (Amount precision) Source # 
Instance details

Defined in Haspara.Accounting.Amount

Methods

(==) :: Amount precision -> Amount precision -> Bool #

(/=) :: Amount precision -> Amount precision -> Bool #

Ord (Amount precision) Source # 
Instance details

Defined in Haspara.Accounting.Amount

Methods

compare :: Amount precision -> Amount precision -> Ordering #

(<) :: Amount precision -> Amount precision -> Bool #

(<=) :: Amount precision -> Amount precision -> Bool #

(>) :: Amount precision -> Amount precision -> Bool #

(>=) :: Amount precision -> Amount precision -> Bool #

max :: Amount precision -> Amount precision -> Amount precision #

min :: Amount precision -> Amount precision -> Amount precision #

type Rep (Amount precision) Source # 
Instance details

Defined in Haspara.Accounting.Amount

type Rep (Amount precision) = D1 ('MetaData "Amount" "Haspara.Accounting.Amount" "haspara-0.0.0.8-83lIPqySeX32MZXT98KoZ2" 'False) (C1 ('MetaCons "Amount" 'PrefixI 'True) (S1 ('MetaSel ('Just "amountSide") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Side) :*: S1 ('MetaSel ('Just "amountValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UnsignedQuantity precision))))

amountDebit :: KnownNat precision => Amount precision -> Maybe (UnsignedQuantity precision) Source #

Returns the debit value of the Amount, if any.

amountCredit :: KnownNat precision => Amount precision -> Maybe (UnsignedQuantity precision) Source #

Returns the credit value of the Amount, if any.

amountFromValue :: KnownNat precision => AccountKind -> Quantity precision -> Amount precision Source #

Builds the Amount for the given value for the given AccountKind.

The value concept here refers to the value of a particular economic event as in the contribution of that event to the net-worth of the entity.

This definition of the value is different than what we refer to in amountFromQuantity. In amountFromQuantity the quantity is simply reflecting the increment or decrement in a particular account of a particular AccountKind.

For example, consider getting a loan: There are two immediate events due to this exchange:

  1. Inflow of cash of some quantity to an AccountKindAsset account.
  2. Inflow of loan contract with some notional value of the same quantity to a 'AccountKindLiability acount.

Let's say, the notional is USD 1,000. Therefore:

  1. Inflow of USD 1,000 to the cash account.
  2. Inflow of a Loan Contract of USD 1,000 to the liability account.

Conventionally, the latter is reflected as follow:

>>> :set -XDataKinds
>>> import Haspara.Quantity
>>> amountFromQuantity AccountKindLiability (mkQuantity 1000 :: Quantity 2)
Amount {amountSide = SideCredit, amountValue = Refined 1000.00}

However, if the call-site is referring to values as in the net effect of the event to the net-worth of the entity, then:

>>> amountFromValue AccountKindLiability (mkQuantity (-1000) :: Quantity 2)
Amount {amountSide = SideCredit, amountValue = Refined 1000.00}

For reference, given:

>>> let valPos = mkQuantity 42 :: Quantity 2
>>> let valNeg = mkQuantity (-42) :: Quantity 2

..., let's consider following events:

We have an inflow and outflow of some assets, respectively:

>>> amountFromValue AccountKindAsset valPos
Amount {amountSide = SideDebit, amountValue = Refined 42.00}
>>> amountFromValue AccountKindAsset valNeg
Amount {amountSide = SideCredit, amountValue = Refined 42.00}

We have some decrease and increase in our liabilities, respectively:

>>> amountFromValue AccountKindLiability valPos
Amount {amountSide = SideDebit, amountValue = Refined 42.00}
>>> amountFromValue AccountKindLiability valNeg
Amount {amountSide = SideCredit, amountValue = Refined 42.00}

We have some increase and decrease in our equity, respectively:

>>> amountFromValue AccountKindEquity valPos
Amount {amountSide = SideCredit, amountValue = Refined 42.00}
>>> amountFromValue AccountKindEquity valNeg
Amount {amountSide = SideDebit, amountValue = Refined 42.00}

We have some profit and loss in our PnL, respectively:

>>> amountFromValue AccountKindRevenue valPos
Amount {amountSide = SideCredit, amountValue = Refined 42.00}
>>> amountFromValue AccountKindRevenue valNeg
Amount {amountSide = SideDebit, amountValue = Refined 42.00}

We have some decrease and increase in our expenses, respectively:

>>> amountFromValue AccountKindExpense valPos
Amount {amountSide = SideCredit, amountValue = Refined 42.00}
>>> amountFromValue AccountKindExpense valNeg
Amount {amountSide = SideDebit, amountValue = Refined 42.00}

valueFromAmount :: KnownNat precision => AccountKind -> Amount precision -> Quantity precision Source #

Returns the value for the given Amount for the given AccountKind.

This is dual to amountFromValue.

For values of positive and negative net-effect on the net-worth of the entity, respectively:

>>> :set -XDataKinds
>>> import Haspara.Quantity
>>> let valPos = mkQuantity 42 :: Quantity 2
>>> let valNeg = mkQuantity (-42) :: Quantity 2

..., for a check function that checks if the roundtrip to a value is successful for a given AccountKind:

>>> let check = \k v -> v == valueFromAmount k (amountFromValue k v)

..., and for the list of AccountKinds.

>>> let kinds = [minBound .. maxBound] :: [AccountKind]
>>> kinds
[AccountKindAsset,AccountKindLiability,AccountKindEquity,AccountKindRevenue,AccountKindExpense]

All checks should pass:

>>> all (\k -> check k valPos && check k valNeg) kinds
True

amountFromQuantity :: KnownNat precision => AccountKind -> Quantity precision -> Amount precision Source #

Builds the Amount value for the given account kind and quantity.

The concept of quantity here refers to the conventional concept of what it means for an Account of a given AccountKind.

For example, a loan of USD 1,000 has an increase in our liabilities. Therefore, the quantity is expected to be positive:

>>> :set -XDataKinds
>>> import Haspara.Quantity
>>> amountFromQuantity AccountKindLiability (mkQuantity 1000 :: Quantity 2)
Amount {amountSide = SideCredit, amountValue = Refined 1000.00}

Note amountFromValue function if you are rather working with values that are conceptually different than the quantity here whereby a value refers to the value of a particular economic event as in the contribution of that event to the net-worth of the entity. Therefore, above example would be reflected as follows to get the same Amount value:

>>> amountFromValue AccountKindLiability (mkQuantity (-1000) :: Quantity 2)
Amount {amountSide = SideCredit, amountValue = Refined 1000.00}

Check amountFromValue documentation for further information.

quantityFromAmount :: KnownNat precision => AccountKind -> Amount precision -> Quantity precision Source #

Returns the quantity for the given amount.

This is dual to amountFromQuantity.