hledger-lib-1.15.2: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Data.Journal

Contents

Description

A Journal is a set of transactions, plus optional related data. This is hledger's primary data object. It is usually parsed from a journal file or other data format (see Hledger.Read).

Synopsis

Parsing helpers

journalBalanceTransactions :: Bool -> Journal -> Either String Journal Source #

Infer any missing amounts (to satisfy balance assignments and to balance transactions) and check that all transactions balance and (optional) all balance assertions pass. Or return an error message (just the first error encountered).

Assumes journalInferCommodityStyles has been called, since those affect transaction balancing.

This does multiple things because amount inferring, balance assignments, balance assertions and posting dates are interdependent.

This can be simplified further. Overview as of 20190219: ****** parseAndFinaliseJournal['] (Cli/Utils.hs), journalAddForecast (Common.hs), budgetJournal (BudgetReport.hs), tests (BalanceReport.hs) ******* journalBalanceTransactions ******** runST ********* runExceptT ********** balanceTransaction (Transaction.hs) *********** balanceTransactionHelper ********** runReaderT *********** balanceTransactionAndCheckAssertionsB ************ addAmountAndCheckAssertionB ************ addOrAssignAmountAndCheckAssertionB ************ balanceTransactionHelper (Transaction.hs) ****** uiCheckBalanceAssertions d uiUIState{aopts=UIOpts{cliopts_=copts}, ajournal=j} (ErrorScreen.hs) ******* journalCheckBalanceAssertions ******** journalBalanceTransactions ****** transactionWizard, postingsBalanced (Add.hs), tests (Transaction.hs) ******* balanceTransaction (Transaction.hs) XXX hledger add won't allow balance assignments + missing amount ? @

journalApplyCommodityStyles :: Journal -> Journal Source #

Choose and apply a consistent display format to the posting amounts in each commodity. Each commodity's format is specified by a commodity format directive, or otherwise inferred from posting amounts as in hledger < 0.28.

commodityStylesFromAmounts :: [Amount] -> Map CommoditySymbol AmountStyle Source #

Given a list of amounts in parse order, build a map from their commodity names to standard commodity display formats.

journalCommodityStyles :: Journal -> Map CommoditySymbol AmountStyle Source #

Get all the amount styles defined in this journal, either declared by a commodity directive or inferred from amounts, as a map from symbol to style. Styles declared by commodity directives take precedence, and these also are guaranteed to know their decimal point character.

journalConvertAmountsToCost :: Journal -> Journal Source #

Convert all this journal's amounts to cost using the transaction prices, if any. The journal's commodity styles are applied to the resulting amounts.

journalReverse :: Journal -> Journal Source #

Reverse all lists of parsed items, which during parsing were prepended to, so that the items are in parse order. Part of post-parse finalisation.

journalSetLastReadTime :: ClockTime -> Journal -> Journal Source #

Set this journal's last read time, ie when its files were last read.

journalPivot :: Text -> Journal -> Journal Source #

Apply the pivot transformation to all postings in a journal, replacing their account name by their value for the given field or tag.

Filtering

filterJournalTransactions :: Query -> Journal -> Journal Source #

Keep only transactions matching the query expression.

filterJournalPostings :: Query -> Journal -> Journal Source #

Keep only postings matching the query expression. This can leave unbalanced transactions.

filterJournalAmounts :: Query -> Journal -> Journal Source #

Within each posting's amount, keep only the parts matching the query. This can leave unbalanced transactions.

filterTransactionAmounts :: Query -> Transaction -> Transaction Source #

Filter out all parts of this transaction's amounts which do not match the query. This can leave the transaction unbalanced.

filterPostingAmount :: Query -> Posting -> Posting Source #

Filter out all parts of this posting's amount which do not match the query.

Mapping

mapJournalTransactions :: (Transaction -> Transaction) -> Journal -> Journal Source #

Apply a transformation to a journal's transactions.

mapJournalPostings :: (Posting -> Posting) -> Journal -> Journal Source #

Apply a transformation to a journal's postings.

mapTransactionPostings :: (Posting -> Posting) -> Transaction -> Transaction Source #

Apply a transformation to a transaction's postings.

Querying

journalAccountNamesUsed :: Journal -> [AccountName] Source #

Sorted unique account names posted to by this journal's transactions.

journalAccountNamesImplied :: Journal -> [AccountName] Source #

Sorted unique account names implied by this journal's transactions - accounts posted to and all their implied parent accounts.

journalAccountNamesDeclared :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives in this journal.

journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives or posted to by transactions in this journal.

journalAccountNamesDeclaredOrImplied :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives, or posted to or implied as parents by transactions in this journal.

journalAccountNames :: Journal -> [AccountName] Source #

Convenience/compatibility alias for journalAccountNamesDeclaredOrImplied.

journalAmounts :: Journal -> [Amount] Source #

Get an ordered list of the amounts in this journal which will influence amount style canonicalisation. These are:

  • amounts in market price directives (in parse order)
  • amounts in postings (in parse order)

Amounts in default commodity directives also influence canonicalisation, but earlier, as amounts are parsed. Amounts in posting prices are not used for canonicalisation.

overJournalAmounts :: (Amount -> Amount) -> Journal -> Journal Source #

Maps over all of the amounts in the journal

traverseJournalAmounts :: Applicative f => (Amount -> f Amount) -> Journal -> f Journal Source #

Traverses over all of the amounts in the journal, in the order indicated by journalAmounts.

journalDateSpan :: Bool -> Journal -> DateSpan Source #

The fully specified date span enclosing the dates (primary or secondary) of all this journal's transactions and postings, or DateSpan Nothing Nothing if there are none.

journalStartDate :: Bool -> Journal -> Maybe Day Source #

The earliest of this journal's transaction and posting dates, or Nothing if there are none.

journalEndDate :: Bool -> Journal -> Maybe Day Source #

The latest of this journal's transaction and posting dates, or Nothing if there are none.

journalDescriptions :: Journal -> [Text] Source #

Unique transaction descriptions used in this journal.

journalTransactionAt :: Journal -> Integer -> Maybe Transaction Source #

Get the transaction with this index (its 1-based position in the input stream), if any.

journalNextTransaction :: Journal -> Transaction -> Maybe Transaction Source #

Get the transaction that appeared immediately after this one in the input stream, if any.

journalPrevTransaction :: Journal -> Transaction -> Maybe Transaction Source #

Get the transaction that appeared immediately before this one in the input stream, if any.

journalPostings :: Journal -> [Posting] Source #

All postings from this journal's transactions, in order.

Standard account types

journalRevenueAccountQuery :: Journal -> Query Source #

A query for accounts in this journal which have been declared as Revenue by account directives, or otherwise for accounts with names matched by the case-insensitive regular expression ^(income|revenue)s?(:|$).

journalExpenseAccountQuery :: Journal -> Query Source #

A query for accounts in this journal which have been declared as Expense by account directives, or otherwise for accounts with names matched by the case-insensitive regular expression ^(income|revenue)s?(:|$).

journalAssetAccountQuery :: Journal -> Query Source #

A query for accounts in this journal which have been declared as Asset by account directives, or otherwise for accounts with names matched by the case-insensitive regular expression ^assets?(:|$).

journalLiabilityAccountQuery :: Journal -> Query Source #

A query for accounts in this journal which have been declared as Liability by account directives, or otherwise for accounts with names matched by the case-insensitive regular expression ^(debts?|liabilit(y|ies))(:|$).

journalEquityAccountQuery :: Journal -> Query Source #

A query for accounts in this journal which have been declared as Equity by account directives, or otherwise for accounts with names matched by the case-insensitive regular expression ^equity(:|$).

journalCashAccountQuery :: Journal -> Query Source #

A query for Cash (-equivalent) accounts in this journal (ie, accounts which appear on the cashflow statement.) This is currently hard-coded to be all the Asset accounts except for those with names containing the case-insensitive regular expression (receivable|:A/R|:fixed).

Misc

canonicalStyleFrom :: [AmountStyle] -> AmountStyle Source #

Given an ordered list of amount styles, choose a canonical style. That is: the style of the first, and the maximum precision of all.

matchpats :: [String] -> String -> Bool Source #

Check if a set of hledger account/description filter patterns matches the given account name or entry description. Patterns are case-insensitive regular expressions. Prefixed with not:, they become anti-patterns.

journalCheckBalanceAssertions :: Journal -> Maybe String Source #

Check any balance assertions in the journal and return an error message if any of them fail (or if the transaction balancing they require fails).

journalUntieTransactions :: Transaction -> Transaction Source #

Untie all transaction-posting knots in this journal, so that eg recursiveSize and GHCI's :sprint can work on it.

journalModifyTransactions :: Journal -> Journal Source #

Apply any transaction modifier rules in the journal (adding automated postings to transactions, eg).

Tests

Orphan instances

Show Journal Source # 
Instance details

Semigroup Journal Source # 
Instance details

Monoid Journal Source # 
Instance details