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

Haspara.Accounting.Ledger

Description

This module provides definitions for postings, ledgers and ledger entries.

Synopsis

Documentation

data Ledger a o (s :: Nat) Source #

Type encoding of a ledger.

Constructors

Ledger 

Instances

Instances details
(Eq a, Eq o) => Eq (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: Ledger a o s -> Ledger a o s -> Bool #

(/=) :: Ledger a o s -> Ledger a o s -> Bool #

(Ord a, Ord o) => Ord (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: Ledger a o s -> Ledger a o s -> Ordering #

(<) :: Ledger a o s -> Ledger a o s -> Bool #

(<=) :: Ledger a o s -> Ledger a o s -> Bool #

(>) :: Ledger a o s -> Ledger a o s -> Bool #

(>=) :: Ledger a o s -> Ledger a o s -> Bool #

max :: Ledger a o s -> Ledger a o s -> Ledger a o s #

min :: Ledger a o s -> Ledger a o s -> Ledger a o s #

(KnownNat s, Show a, Show o) => Show (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> Ledger a o s -> ShowS #

show :: Ledger a o s -> String #

showList :: [Ledger a o s] -> ShowS #

Generic (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (Ledger a o s) :: Type -> Type #

Methods

from :: Ledger a o s -> Rep (Ledger a o s) x #

to :: Rep (Ledger a o s) x -> Ledger a o s #

(ToJSON a, ToJSON o, KnownNat s) => ToJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

toJSON :: Ledger a o s -> Value #

toEncoding :: Ledger a o s -> Encoding #

toJSONList :: [Ledger a o s] -> Value #

toEncodingList :: [Ledger a o s] -> Encoding #

(FromJSON a, FromJSON o, KnownNat s) => FromJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

parseJSON :: Value -> Parser (Ledger a o s) #

parseJSONList :: Value -> Parser [Ledger a o s] #

type Rep (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (Ledger a o s) = D1 ('MetaData "Ledger" "Haspara.Accounting.Ledger" "haspara-0.0.0.3-4zv1bokQoxCFAyBHZ5p8oz" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ledgerAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Account a)) :*: S1 ('MetaSel ('Just "ledgerOpening") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))) :*: (S1 ('MetaSel ('Just "ledgerClosing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s)) :*: S1 ('MetaSel ('Just "ledgerRunning") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [LedgerItem o s]))))

data LedgerItem o (s :: Nat) Source #

Type encoding of a ledger item.

Constructors

LedgerItem 

Fields

Instances

Instances details
Eq o => Eq (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: LedgerItem o s -> LedgerItem o s -> Bool #

(/=) :: LedgerItem o s -> LedgerItem o s -> Bool #

Ord o => Ord (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: LedgerItem o s -> LedgerItem o s -> Ordering #

(<) :: LedgerItem o s -> LedgerItem o s -> Bool #

(<=) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>=) :: LedgerItem o s -> LedgerItem o s -> Bool #

max :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

min :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

(Show o, KnownNat s) => Show (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> LedgerItem o s -> ShowS #

show :: LedgerItem o s -> String #

showList :: [LedgerItem o s] -> ShowS #

Generic (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (LedgerItem o s) :: Type -> Type #

Methods

from :: LedgerItem o s -> Rep (LedgerItem o s) x #

to :: Rep (LedgerItem o s) x -> LedgerItem o s #

(ToJSON o, KnownNat s) => ToJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

(FromJSON o, KnownNat s) => FromJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) = D1 ('MetaData "LedgerItem" "Haspara.Accounting.Ledger" "haspara-0.0.0.3-4zv1bokQoxCFAyBHZ5p8oz" 'False) (C1 ('MetaCons "LedgerItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerItemEntry") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Entry o s)) :*: S1 ('MetaSel ('Just "ledgerItemBalance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))))

mkLedger :: KnownNat s => Account a -> Quantity s -> [Entry o s] -> Ledger a o s Source #

Creates a ledger from a given list of Entry values.

addEntry :: KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s Source #

Adds a new entry to a ledger.

newtype Posting a o (s :: Nat) Source #

Type encoding for a posting.

>>> :set -XDataKinds
>>> import Haspara.Accounting
>>> import Refined
>>> import qualified Data.Aeson as Aeson
>>> import qualified Data.List.NonEmpty as NE
>>> let date = read "2021-01-01"
>>> let oid = 1 :: Int
>>> let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>> let event = EventDecrement date oid qty
>>> let account = Account AccountKindAsset ("Cash" :: String, 1 ::Int)
>>> let posting =  Posting . NE.fromList $ [(event, account)]
>>> let json = Aeson.encode posting
>>> json
"[[{\"qty\":42.0,\"type\":\"DECREMENT\",\"obj\":1,\"date\":\"2021-01-01\"},{\"kind\":\"ASSET\",\"object\":[\"Cash\",1]}]]"
>>> Aeson.decode json :: Maybe (Posting (String, Int) Int 2)
Just (Posting ((EventDecrement 2021-01-01 1 (Refined 42.00),Account {accountKind = AccountKindAsset, accountObject = ("Cash",1)}) :| []))
>>> Aeson.decode json == Just posting
True

Constructors

Posting (NonEmpty (Event o s, Account a)) 

Instances

Instances details
(Eq o, Eq a) => Eq (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: Posting a o s -> Posting a o s -> Bool #

(/=) :: Posting a o s -> Posting a o s -> Bool #

(Ord o, Ord a) => Ord (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: Posting a o s -> Posting a o s -> Ordering #

(<) :: Posting a o s -> Posting a o s -> Bool #

(<=) :: Posting a o s -> Posting a o s -> Bool #

(>) :: Posting a o s -> Posting a o s -> Bool #

(>=) :: Posting a o s -> Posting a o s -> Bool #

max :: Posting a o s -> Posting a o s -> Posting a o s #

min :: Posting a o s -> Posting a o s -> Posting a o s #

(KnownNat s, Show o, Show a) => Show (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> Posting a o s -> ShowS #

show :: Posting a o s -> String #

showList :: [Posting a o s] -> ShowS #

Generic (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (Posting a o s) :: Type -> Type #

Methods

from :: Posting a o s -> Rep (Posting a o s) x #

to :: Rep (Posting a o s) x -> Posting a o s #

(ToJSON a, ToJSON o, KnownNat s) => ToJSON (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

toJSON :: Posting a o s -> Value #

toEncoding :: Posting a o s -> Encoding #

toJSONList :: [Posting a o s] -> Value #

toEncodingList :: [Posting a o s] -> Encoding #

(FromJSON a, FromJSON o, KnownNat s) => FromJSON (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

parseJSON :: Value -> Parser (Posting a o s) #

parseJSONList :: Value -> Parser [Posting a o s] #

type Rep (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (Posting a o s) = D1 ('MetaData "Posting" "Haspara.Accounting.Ledger" "haspara-0.0.0.3-4zv1bokQoxCFAyBHZ5p8oz" 'True) (C1 ('MetaCons "Posting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Event o s, Account a)))))

postingEvents :: KnownNat s => Posting a o s -> [o] Source #

Returns the list of posting event sources.

post :: KnownNat s => Posting a o s -> [(Account a, Entry o s)] Source #

Posts an event.

data Entry o (s :: Nat) Source #

Encoding of a posting entry.

>>> :set -XDataKinds
>>> import Refined
>>> let date = read "2021-01-01"
>>> let oid = 1 :: Int
>>> let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>> let entry = EntryDebit date oid qty
>>> let json = Aeson.encode entry
>>> json
"{\"qty\":42.0,\"type\":\"DEBIT\",\"obj\":1,\"date\":\"2021-01-01\"}"
>>> Aeson.decode json :: Maybe (Entry Int 2)
Just (EntryDebit 2021-01-01 1 (Refined 42.00))
>>> Aeson.decode json == Just entry
True

Instances

Instances details
Eq o => Eq (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: Entry o s -> Entry o s -> Bool #

(/=) :: Entry o s -> Entry o s -> Bool #

Ord o => Ord (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: Entry o s -> Entry o s -> Ordering #

(<) :: Entry o s -> Entry o s -> Bool #

(<=) :: Entry o s -> Entry o s -> Bool #

(>) :: Entry o s -> Entry o s -> Bool #

(>=) :: Entry o s -> Entry o s -> Bool #

max :: Entry o s -> Entry o s -> Entry o s #

min :: Entry o s -> Entry o s -> Entry o s #

(Show o, KnownNat s) => Show (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> Entry o s -> ShowS #

show :: Entry o s -> String #

showList :: [Entry o s] -> ShowS #

(ToJSON o, KnownNat s) => ToJSON (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

toJSON :: Entry o s -> Value #

toEncoding :: Entry o s -> Encoding #

toJSONList :: [Entry o s] -> Value #

toEncodingList :: [Entry o s] -> Encoding #

(FromJSON o, KnownNat s) => FromJSON (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

parseJSON :: Value -> Parser (Entry o s) #

parseJSONList :: Value -> Parser [Entry o s] #

entryDate :: KnownNat s => Entry o s -> Day Source #

Returns the date of the posting entry.

entryQuantity :: KnownNat s => Entry o s -> Quantity s Source #

Returns the quantity of the posting entry.

entryObject :: KnownNat s => Entry o s -> o Source #

Returns the source object of the posting entry.

entryDebit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s) Source #

Returns the debit quantity of the posting entry.

entryCredit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s) Source #

Returns the credit quantity of the posting entry.

buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s Source #

Consumes an event and a type of account, and produces a posting entry.

Note the following map as a guide:

Kind of accountDebitCredit
AssetIncreaseDecrease
LiabilityDecreaseIncrease
Equity/CapitalDecreaseIncrease
Income/RevenueDecreaseIncrease
ExpenseCostDividendIncreaseDecrease