Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides definitions for postings, ledgers and ledger entries.
Synopsis
- data Ledger a o (s :: Nat) = Ledger {
- ledgerAccount :: !(Account a)
- ledgerOpening :: !(Quantity s)
- ledgerClosing :: !(Quantity s)
- ledgerRunning :: ![LedgerItem o s]
- data LedgerItem o (s :: Nat) = LedgerItem {
- ledgerItemEntry :: !(Entry o s)
- ledgerItemBalance :: !(Quantity s)
- mkLedger :: KnownNat s => Account a -> Quantity s -> [Entry o s] -> Ledger a o s
- addEntry :: KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s
- newtype Posting a o (s :: Nat) = Posting (NonEmpty (Event o s, Account a))
- postingEvents :: KnownNat s => Posting a o s -> [o]
- post :: KnownNat s => Posting a o s -> [(Account a, Entry o s)]
- data Entry o (s :: Nat)
- = EntryDebit Day o (UnsignedQuantity s)
- | EntryCredit Day o (UnsignedQuantity s)
- entryDate :: KnownNat s => Entry o s -> Day
- entryQuantity :: KnownNat s => Entry o s -> Quantity s
- entryObject :: KnownNat s => Entry o s -> o
- entryDebit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s)
- entryCredit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s)
- buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s
Documentation
data Ledger a o (s :: Nat) Source #
Type encoding of a ledger.
Ledger | |
|
Instances
data LedgerItem o (s :: Nat) Source #
Type encoding of a ledger item.
LedgerItem | |
|
Instances
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
Instances
postingEvents :: KnownNat s => Posting a o s -> [o] Source #
Returns the list of posting event sources.
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
EntryDebit Day o (UnsignedQuantity s) | |
EntryCredit Day o (UnsignedQuantity s) |
Instances
Eq o => Eq (Entry o s) Source # | |
Ord o => Ord (Entry o s) Source # | |
Defined in Haspara.Accounting.Ledger | |
(Show o, KnownNat s) => Show (Entry o s) Source # | |
(ToJSON o, KnownNat s) => ToJSON (Entry o s) Source # | |
Defined in Haspara.Accounting.Ledger | |
(FromJSON o, KnownNat s) => FromJSON (Entry o s) Source # | |
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 account | Debit | Credit |
Asset | Increase | Decrease |
Liability | Decrease | Increase |
Equity/Capital | Decrease | Increase |
Income/Revenue | Decrease | Increase |
ExpenseCostDividend | Increase | Decrease |