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

Haspara.Accounting.Journal

Description

This module provides data definitions and functions to work with journal entries.

Synopsis

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.

Constructors

Journal 

Fields

Instances

Instances details
(KnownNat precision, Show account, Show event) => Show (Journal precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

showsPrec :: Int -> Journal precision account event -> ShowS #

show :: Journal precision account event -> String #

showList :: [Journal precision account event] -> ShowS #

Generic (Journal precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Associated Types

type Rep (Journal precision account event) :: Type -> Type #

Methods

from :: Journal precision account event -> Rep (Journal precision account event) x #

to :: Rep (Journal precision account event) x -> Journal precision account event #

(KnownNat precision, ToJSON account, ToJSON event) => ToJSON (Journal precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

toJSON :: Journal precision account event -> Value #

toEncoding :: Journal precision account event -> Encoding #

toJSONList :: [Journal precision account event] -> Value #

toEncodingList :: [Journal precision account event] -> Encoding #

(KnownNat precision, FromJSON account, FromJSON event) => FromJSON (Journal precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

parseJSON :: Value -> Parser (Journal precision account event) #

parseJSONList :: Value -> Parser [Journal precision account event] #

type Rep (Journal precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

type Rep (Journal precision account event) = D1 ('MetaData "Journal" "Haspara.Accounting.Journal" "haspara-0.0.0.5-EkkfyzMRwPgIJNppmBSdYM" 'True) (C1 ('MetaCons "Journal" 'PrefixI 'True) (S1 ('MetaSel ('Just "journalEntries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JournalEntry precision account event])))

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 JournalEntryItems. Journal entry definition is polymorphic over the precision of the monetary quantities, the account and event objects.

Constructors

JournalEntry 

Instances

Instances details
(KnownNat precision, Show account, Show event) => Show (JournalEntry precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

showsPrec :: Int -> JournalEntry precision account event -> ShowS #

show :: JournalEntry precision account event -> String #

showList :: [JournalEntry precision account event] -> ShowS #

Generic (JournalEntry precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Associated Types

type Rep (JournalEntry precision account event) :: Type -> Type #

Methods

from :: JournalEntry precision account event -> Rep (JournalEntry precision account event) x #

to :: Rep (JournalEntry precision account event) x -> JournalEntry precision account event #

(KnownNat precision, ToJSON account, ToJSON event) => ToJSON (JournalEntry precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

toJSON :: JournalEntry precision account event -> Value #

toEncoding :: JournalEntry precision account event -> Encoding #

toJSONList :: [JournalEntry precision account event] -> Value #

toEncodingList :: [JournalEntry precision account event] -> Encoding #

(KnownNat precision, FromJSON account, FromJSON event) => FromJSON (JournalEntry precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

parseJSON :: Value -> Parser (JournalEntry precision account event) #

parseJSONList :: Value -> Parser [JournalEntry precision account event] #

type Rep (JournalEntry precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

type Rep (JournalEntry precision account event) = D1 ('MetaData "JournalEntry" "Haspara.Accounting.Journal" "haspara-0.0.0.5-EkkfyzMRwPgIJNppmBSdYM" 'False) (C1 ('MetaCons "JournalEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "journalEntryId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "journalEntryDate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day)) :*: (S1 ('MetaSel ('Just "journalEntryItems") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [JournalEntryItem precision account event]) :*: S1 ('MetaSel ('Just "journalEntryDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

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.

Constructors

JournalEntryItem 

Fields

Instances

Instances details
(Eq account, Eq event) => Eq (JournalEntryItem precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

(==) :: 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 # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

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 # 
Instance details

Defined in Haspara.Accounting.Journal

Associated Types

type Rep (JournalEntryItem precision account event) :: Type -> Type #

Methods

from :: JournalEntryItem precision account event -> Rep (JournalEntryItem precision account event) x #

to :: Rep (JournalEntryItem precision account event) x -> JournalEntryItem precision account event #

(KnownNat precision, ToJSON account, ToJSON event) => ToJSON (JournalEntryItem precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

toJSON :: JournalEntryItem precision account event -> Value #

toEncoding :: JournalEntryItem precision account event -> Encoding #

toJSONList :: [JournalEntryItem precision account event] -> Value #

toEncodingList :: [JournalEntryItem precision account event] -> Encoding #

(KnownNat precision, FromJSON account, FromJSON event) => FromJSON (JournalEntryItem precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

Methods

parseJSON :: Value -> Parser (JournalEntryItem precision account event) #

parseJSONList :: Value -> Parser [JournalEntryItem precision account event] #

type Rep (JournalEntryItem precision account event) Source # 
Instance details

Defined in Haspara.Accounting.Journal

type Rep (JournalEntryItem precision account event) = D1 ('MetaData "JournalEntryItem" "Haspara.Accounting.Journal" "haspara-0.0.0.5-EkkfyzMRwPgIJNppmBSdYM" '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.