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

Haspara.Accounting.Balance

Description

This module provides definitions for balances used as in accounting.

Synopsis

Documentation

data Balance (precision :: Nat) Source #

Data definition for balances.

This definition is similar to Amount, however, the value is allowed to be negative to reflect "Negative Balance" phenomenon.

See https://www.accountingtools.com/articles/what-is-a-negative-balance.html

Constructors

Balance 

Fields

Instances

Instances details
Eq (Balance precision) Source # 
Instance details

Defined in Haspara.Accounting.Balance

Methods

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

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

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

Defined in Haspara.Accounting.Balance

Methods

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

show :: Balance precision -> String #

showList :: [Balance precision] -> ShowS #

Generic (Balance precision) Source # 
Instance details

Defined in Haspara.Accounting.Balance

Associated Types

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

Methods

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

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

KnownNat precision => ToJSON (Balance precision) Source #

ToJSON instance for Balance.

For normal balances:

>>> import Haspara.Accounting.Side
>>> import Haspara.Quantity
>>> Aeson.encode (Balance SideDebit (mkQuantity 42 :: Quantity 2))
"{\"side\":\"db\",\"value\":42.0}"
>>> Aeson.encode (Balance SideCredit (mkQuantity 42 :: Quantity 2))
"{\"side\":\"cr\",\"value\":42.0}"
>>> Aeson.eitherDecode (Aeson.encode (Balance SideDebit (mkQuantity 42 :: Quantity 2))) :: Either String (Balance 2)
Right (Balance {balanceSide = SideDebit, balanceValue = 42.00})
>>> Aeson.eitherDecode (Aeson.encode (Balance SideCredit (mkQuantity 42 :: Quantity 2))) :: Either String (Balance 2)
Right (Balance {balanceSide = SideCredit, balanceValue = 42.00})

For negative balances:

>>> Aeson.encode (Balance SideDebit (mkQuantity (-42) :: Quantity 2))
"{\"side\":\"db\",\"value\":-42.0}"
>>> Aeson.encode (Balance SideCredit (mkQuantity (-42) :: Quantity 2))
"{\"side\":\"cr\",\"value\":-42.0}"
>>> Aeson.eitherDecode (Aeson.encode (Balance SideDebit (mkQuantity (-42) :: Quantity 2))) :: Either String (Balance 2)
Right (Balance {balanceSide = SideDebit, balanceValue = -42.00})
>>> Aeson.eitherDecode (Aeson.encode (Balance SideCredit (mkQuantity (-42) :: Quantity 2))) :: Either String (Balance 2)
Right (Balance {balanceSide = SideCredit, balanceValue = -42.00})
Instance details

Defined in Haspara.Accounting.Balance

Methods

toJSON :: Balance precision -> Value #

toEncoding :: Balance precision -> Encoding #

toJSONList :: [Balance precision] -> Value #

toEncodingList :: [Balance precision] -> Encoding #

KnownNat precision => FromJSON (Balance precision) Source #

FromJSON instance for Balance.

For normal balances:

>>> Aeson.eitherDecode "{\"side\": \"db\", \"value\": 42}" :: Either String (Balance 2)
Right (Balance {balanceSide = SideDebit, balanceValue = 42.00})
>>> Aeson.eitherDecode "{\"side\": \"cr\", \"value\": 42}" :: Either String (Balance 2)
Right (Balance {balanceSide = SideCredit, balanceValue = 42.00})

For negative balances:

>>> Aeson.eitherDecode "{\"side\": \"db\", \"value\": -42}" :: Either String (Balance 2)
Right (Balance {balanceSide = SideDebit, balanceValue = -42.00})
>>> Aeson.eitherDecode "{\"side\": \"cr\", \"value\": -42}" :: Either String (Balance 2)
Right (Balance {balanceSide = SideCredit, balanceValue = -42.00})
Instance details

Defined in Haspara.Accounting.Balance

Methods

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

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

type Rep (Balance precision) Source # 
Instance details

Defined in Haspara.Accounting.Balance

type Rep (Balance precision) = D1 ('MetaData "Balance" "Haspara.Accounting.Balance" "haspara-0.0.0.4-91kyQ1gsJrx6JOOKY5ajCi" 'False) (C1 ('MetaCons "Balance" 'PrefixI 'True) (S1 ('MetaSel ('Just "balanceSide") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Side) :*: S1 ('MetaSel ('Just "balanceValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity precision))))

balanceDebit :: KnownNat precision => Balance precision -> Maybe (Quantity precision) Source #

Returns the debit quantity, if any.

balanceCredit :: KnownNat precision => Balance precision -> Maybe (Quantity precision) Source #

Returns the credit quantity, if any.

updateBalance :: KnownNat precision => Balance precision -> Amount precision -> Balance precision Source #

Updates the balance with the given amount.

>>> import Haspara.Accounting.Amount
>>> import Haspara.Accounting.Side
>>> import Refined.Unsafe
>>> let balance = Balance SideDebit 42 :: Balance 2
>>> balance
Balance {balanceSide = SideDebit, balanceValue = 42.00}
>>> let amountDebit = Amount SideDebit (unsafeRefine 10) :: Amount 2
>>> amountDebit
Amount {amountSide = SideDebit, amountValue = Refined 10.00}
>>> let amountCredit = Amount SideCredit (unsafeRefine 10) :: Amount 2
>>> amountCredit
Amount {amountSide = SideCredit, amountValue = Refined 10.00}
>>> updateBalance balance amountDebit
Balance {balanceSide = SideDebit, balanceValue = 52.00}
>>> updateBalance balance amountCredit
Balance {balanceSide = SideDebit, balanceValue = 32.00}

amountFromBalance :: KnownNat precision => Balance precision -> Amount precision Source #

Converts the balance to amount.

>>> import Haspara.Accounting.Side
>>> amountFromBalance (Balance SideDebit 42 :: Balance 2)
Amount {amountSide = SideDebit, amountValue = Refined 42.00}
>>> amountFromBalance (Balance SideDebit (-42) :: Balance 2)
Amount {amountSide = SideCredit, amountValue = Refined 42.00}
>>> amountFromBalance (Balance SideCredit 42 :: Balance 2)
Amount {amountSide = SideCredit, amountValue = Refined 42.00}
>>> amountFromBalance (Balance SideCredit (-42) :: Balance 2)
Amount {amountSide = SideDebit, amountValue = Refined 42.00}

quantityFromBalance :: KnownNat precision => AccountKind -> Balance precision -> Quantity precision Source #

Returns the quantity of the balance given the account kind.

See quantityFromAmount for the meaning of quantity.

valueFromBalance :: KnownNat precision => AccountKind -> Balance precision -> Quantity precision Source #

Returns the value of the balance given the account kind.

See valueFromAmount for the meaning of quantity.