Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides data definitions and functions to work with journal entries.
Synopsis
- newtype Journal (precision :: Nat) account event = Journal {
- journalEntries :: [JournalEntry precision account event]
- data JournalEntry (precision :: Nat) account event = JournalEntry {
- journalEntryId :: !Text
- journalEntryDate :: !Day
- journalEntryItems :: ![JournalEntryItem precision account event]
- journalEntryDescription :: !Text
- journalEntryTotalDebit :: KnownNat precision => JournalEntry precision account event -> UnsignedQuantity precision
- journalEntryTotalCredit :: KnownNat precision => JournalEntry precision account event -> UnsignedQuantity precision
- isJournalEntryBalanced :: KnownNat precision => JournalEntry precision account event -> Bool
- data JournalEntryItem (precision :: Nat) account event = JournalEntryItem {
- journalEntryItemAmount :: !(Amount precision)
- journalEntryItemAccount :: !(Account account)
- journalEntryItemEvent :: !event
- mkJournalEntryItemFromQuantity :: KnownNat precision => Quantity precision -> Account account -> event -> JournalEntryItem precision account event
- mkJournalEntryItemFromValue :: KnownNat precision => Quantity precision -> Account account -> event -> JournalEntryItem precision account event
Documentation
newtype Journal (precision :: Nat) account event Source #
Data definition for the journal entries of interest (like a general ledger.)
A Journal
is a list of JournalEntry
records which are polymorphic over
the precision of the monetary quantities, the account and event objects.
Journal | |
|
data JournalEntry (precision :: Nat) account event Source #
Data definition for a journal entry.
A journal entry has a (unique) identifier, date and description, and a list
of JournalEntryItem
s. Journal entry definition is polymorphic over the
precision of the monetary quantities, the account and event objects.
JournalEntry | |
|
Instances
(KnownNat precision, Show account, Show event) => Show (JournalEntry precision account event) Source # | |
Defined in Haspara.Accounting.Journal showsPrec :: Int -> JournalEntry precision account event -> ShowS # show :: JournalEntry precision account event -> String # showList :: [JournalEntry precision account event] -> ShowS # |
journalEntryTotalDebit :: KnownNat precision => JournalEntry precision account event -> UnsignedQuantity precision Source #
Returns the total debit amount of a journal entry.
journalEntryTotalCredit :: KnownNat precision => JournalEntry precision account event -> UnsignedQuantity precision Source #
Returns the total credit amount of a journal entry.
isJournalEntryBalanced :: KnownNat precision => JournalEntry precision account event -> Bool Source #
Predicate to check if a journal entry is balanced or not.
The logical check is indeed whether the total debit amount is equal to the total credit amount or not.
data JournalEntryItem (precision :: Nat) account event Source #
Data definition for a journal entry item.
A journal entry item has a Side
, an unsigned quantity as amount, an account
that it belongs to and the event the item is originating from. Journal entry
item definition is polymorphic over the precision of the monetary quantities,
the account and event objects.
JournalEntryItem | |
|
Instances
(Eq account, Eq event) => Eq (JournalEntryItem precision account event) Source # | |
Defined in Haspara.Accounting.Journal (==) :: JournalEntryItem precision account event -> JournalEntryItem precision account event -> Bool # (/=) :: JournalEntryItem precision account event -> JournalEntryItem precision account event -> Bool # | |
(KnownNat precision, Show account, Show event) => Show (JournalEntryItem precision account event) Source # | |
Defined in Haspara.Accounting.Journal showsPrec :: Int -> JournalEntryItem precision account event -> ShowS # show :: JournalEntryItem precision account event -> String # showList :: [JournalEntryItem precision account event] -> ShowS # | |
Generic (JournalEntryItem precision account event) Source # | |
Defined in Haspara.Accounting.Journal type Rep (JournalEntryItem precision account event) :: Type -> Type # from :: JournalEntryItem precision account event -> Rep (JournalEntryItem precision account event) x # to :: Rep (JournalEntryItem precision account event) x -> JournalEntryItem precision account event # | |
type Rep (JournalEntryItem precision account event) Source # | |
Defined in Haspara.Accounting.Journal type Rep (JournalEntryItem precision account event) = D1 ('MetaData "JournalEntryItem" "Haspara.Accounting.Journal" "haspara-0.0.0.4-91kyQ1gsJrx6JOOKY5ajCi" 'False) (C1 ('MetaCons "JournalEntryItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "journalEntryItemAmount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Amount precision)) :*: (S1 ('MetaSel ('Just "journalEntryItemAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Account account)) :*: S1 ('MetaSel ('Just "journalEntryItemEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 event)))) |
mkJournalEntryItemFromQuantity :: KnownNat precision => Quantity precision -> Account account -> event -> JournalEntryItem precision account event Source #
Creates a JournalEntryItem
from the given signed quantity, the account
it belongs to and the event it is originating from.
The quantity is defined as in amountFromQuantity
function.
mkJournalEntryItemFromValue :: KnownNat precision => Quantity precision -> Account account -> event -> JournalEntryItem precision account event Source #
Creates a JournalEntryItem
from the given signed value, the account it
belongs to and the event it is originating from.
The value is defined as in amountFromValue
function.