Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a collection of definitions for a rudimentary accounting functionality.
Synopsis
- data Account o = Account {
- accountKind :: !AccountKind
- accountObject :: !o
- data AccountKind
- accountKindText :: AccountKind -> Text
- data Entry o (s :: Nat)
- = EntryDebit Day o (UnsignedQuantity s)
- | EntryCredit Day o (UnsignedQuantity s)
- buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s
- data Event o (s :: Nat)
- = EventDecrement Day o (UnsignedQuantity s)
- | EventIncrement Day o (UnsignedQuantity s)
- eventDate :: KnownNat s => Event o s -> Day
- eventObject :: KnownNat s => Event o s -> o
- negateEvent :: KnownNat s => Event o s -> Event o s
- mkEvent :: MonadError String m => KnownNat s => Day -> o -> Quantity s -> m (Event 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 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
- entryDate :: KnownNat s => Entry o s -> Day
- entryObject :: KnownNat s => Entry o s -> o
- entryQuantity :: KnownNat s => Entry o s -> Quantity s
- entryDebit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s)
- entryCredit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s)
Documentation
Type encoding for account values.
This definition provides both the AccountKind
and an arbitrary object
identifying the account. This arbitrary nature provides flexibility to
use-site to use its own account identity and accompanying information when
required.
>>>
let acc = Account AccountKindAsset (1 ::Int)
>>>
Data.Aeson.encode acc
"{\"kind\":\"ASSET\",\"object\":1}">>>
Data.Aeson.decode @(Account Int) (Data.Aeson.encode acc)
Just (Account {accountKind = AccountKindAsset, accountObject = 1})>>>
Data.Aeson.decode (Data.Aeson.encode acc) == Just acc
True
Account | |
|
Instances
Eq o => Eq (Account o) Source # | |
Ord o => Ord (Account o) Source # | |
Defined in Haspara.Accounting.Account | |
Show o => Show (Account o) Source # | |
Generic (Account o) Source # | |
Hashable o => Hashable (Account o) Source # | |
Defined in Haspara.Accounting.Account | |
ToJSON o => ToJSON (Account o) Source # | |
Defined in Haspara.Accounting.Account | |
FromJSON o => FromJSON (Account o) Source # | |
type Rep (Account o) Source # | |
Defined in Haspara.Accounting.Account type Rep (Account o) = D1 ('MetaData "Account" "Haspara.Accounting.Account" "haspara-0.0.0.3-4zv1bokQoxCFAyBHZ5p8oz" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (S1 ('MetaSel ('Just "accountKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AccountKind) :*: S1 ('MetaSel ('Just "accountObject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 o))) |
data AccountKind Source #
Type encoding for ledger account type.
This type covers both balance sheet and income statement account types:
- For balance sheet accounts:
- Asset (
AccountKindAsset
) - Liability (
AccountKindLiability
) - Equity (
AccountKindEquity
) - For income statement accounts:
- Revenue (
AccountKindRevenue
) - Expense (
AccountKindExpense
)
FromJSON
and ToJSON
instances, too:
>>>
Data.Aeson.decode @AccountKind "\"ASSET\""
Just AccountKindAsset>>>
Data.Aeson.decode @AccountKind "\"LIABILITY\""
Just AccountKindLiability>>>
Data.Aeson.decode @AccountKind "\"EQUITY\""
Just AccountKindEquity>>>
Data.Aeson.decode @AccountKind "\"REVENUE\""
Just AccountKindRevenue>>>
Data.Aeson.decode @AccountKind "\"EXPENSE\""
Just AccountKindExpense>>>
Data.Aeson.encode AccountKindAsset
"\"ASSET\"">>>
Data.Aeson.encode AccountKindLiability
"\"LIABILITY\"">>>
Data.Aeson.encode AccountKindEquity
"\"EQUITY\"">>>
Data.Aeson.encode AccountKindRevenue
"\"REVENUE\"">>>
Data.Aeson.encode AccountKindExpense
"\"EXPENSE\""
Instances
accountKindText :: AccountKind -> Text Source #
Provides textual representation of a given AccountKind
.
>>>
accountKindText AccountKindAsset
"Asset">>>
accountKindText AccountKindLiability
"Liability">>>
accountKindText AccountKindEquity
"Equity">>>
accountKindText AccountKindRevenue
"Revenue">>>
accountKindText AccountKindExpense
"Expense"
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 # | |
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 |
data Event o (s :: Nat) Source #
Type encoding of an economic increment/decrement event.
The event explicitly carries the date and quantity information along with a parameterized, arbitrary object providing the source of the event.
>>>
:set -XDataKinds
>>>
let date = read "2021-01-01"
>>>
let oid = 1 :: Int
>>>
let qty = $$(Refined.refineTH 42) :: UnsignedQuantity 2
>>>
let event = EventDecrement date oid qty
>>>
let json = Data.Aeson.encode event
>>>
json
"{\"qty\":42.0,\"type\":\"DECREMENT\",\"obj\":1,\"date\":\"2021-01-01\"}">>>
Data.Aeson.decode @(Event Int 2) json
Just (EventDecrement 2021-01-01 1 (Refined 42.00))>>>
Data.Aeson.decode json == Just event
True
EventDecrement Day o (UnsignedQuantity s) | |
EventIncrement Day o (UnsignedQuantity s) |
Instances
eventObject :: KnownNat s => Event o s -> o Source #
Returns the source object of the event.
:: MonadError String m | |
=> KnownNat s | |
=> Day | Date of the event. |
-> o | Source object of the event. |
-> Quantity s | Quantity of the event. |
-> m (Event o s) |
Smart constuctor for Event
values.
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 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.
entryObject :: KnownNat s => Entry o s -> o Source #
Returns the source object of the posting entry.
entryQuantity :: KnownNat s => Entry o s -> Quantity s Source #
Returns the quantity 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.