Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Account o = Account {
- accountKind :: !AccountKind
- accountObject :: !o
- data AccountKind
- accountKindText :: AccountKind -> Text
- data Entry o (s :: Nat)
- = EntryDebit Date o (UnsignedQuantity s)
- | EntryCredit Date o (UnsignedQuantity s)
- buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s
- data Event o (s :: Nat)
- = EventDecrement Date o (UnsignedQuantity s)
- | EventIncrement Date o (UnsignedQuantity s)
- eventDate :: KnownNat s => Event o s -> Date
- eventObject :: KnownNat s => Event o s -> o
- negateEvent :: KnownNat s => Event o s -> Event o s
- mkEvent :: (MonadError String m, KnownNat s) => Date -> 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)]
- type UnsignedQuantity s = Refined NonNegative (Quantity 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 -> Date
- 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
Account model.
>>>
import Haspara.Accounting.AccountKind (AccountKind(..))
>>>
import qualified Data.Aeson as Aeson
>>>
let acc = Account AccountKindAsset (1 ::Int)
>>>
Aeson.encode acc
"{\"kind\":\"ASSET\",\"object\":1}">>>
Aeson.decode (Aeson.encode acc) :: Maybe (Account Int)
Just (Account {accountKind = AccountKindAsset, accountObject = 1})>>>
Aeson.decode (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.1-GIZpgp6So3jGG6B29GnUaf" '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 #
Instances
accountKindText :: AccountKind -> Text Source #
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,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DEBIT\"}">>>
Aeson.decode json :: Maybe (Entry Int 2)
Just (EntryDebit 2021-01-01 1 (Refined 42.00))>>>
Aeson.decode json == Just entry
True
EntryDebit Date o (UnsignedQuantity s) | |
EntryCredit Date o (UnsignedQuantity s) |
Instances
buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s Source #
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 #
Encoding of an increment/decrement event.
>>>
:set -XDataKinds
>>>
import Refined
>>>
let date = read "2021-01-01"
>>>
let oid = 1 :: Int
>>>
let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>>
let event = EventDecrement date oid qty
>>>
let json = Aeson.encode event
>>>
json
"{\"qty\":42.0,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DECREMENT\"}">>>
Aeson.decode json :: Maybe (Event Int 2)
Just (EventDecrement 2021-01-01 1 (Refined 42.00))>>>
Aeson.decode json == Just event
True
EventDecrement Date o (UnsignedQuantity s) | |
EventIncrement Date o (UnsignedQuantity s) |
Instances
eventObject :: KnownNat s => Event o s -> o Source #
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,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DECREMENT\"},{\"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 #
type UnsignedQuantity s = Refined NonNegative (Quantity s) Source #
data Ledger a o (s :: Nat) Source #
Ledger | |
|
Instances
data LedgerItem o (s :: Nat) Source #
LedgerItem | |
|
Instances
entryObject :: KnownNat s => Entry o s -> o Source #
entryDebit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s) Source #
entryCredit :: KnownNat s => Entry o s -> Maybe (UnsignedQuantity s) Source #