hledger-lib-1.28: A reusable library providing the core functionality of hledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Data.Journal

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

type JournalParser m a = StateT Journal (ParsecT HledgerParseErrorData Text m) a Source #

A parser of text that runs in some monad, keeping a Journal as state.

type ErroringJournalParser m a = StateT Journal (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m)) a Source #

A parser of text that runs in some monad, keeping a Journal as state, that can throw an exception to end parsing, preventing further parser backtracking.

journalInferMarketPricesFromTransactions :: Journal -> Journal Source #

Infer transaction-implied market prices from commodity-exchanging transactions, if any. It's best to call this after transactions have been balanced and posting amounts have appropriate prices attached.

journalApplyCommodityStyles :: Journal -> Either String Journal Source #

Choose and apply a consistent display style to the posting amounts in each commodity (see journalCommodityStyles). Can return an error message eg if inconsistent number formats are found.

commodityStylesFromAmounts :: [Amount] -> Either String (Map CommoditySymbol AmountStyle) Source #

Given a list of amounts, in parse order (roughly speaking; see journalStyleInfluencingAmounts), build a map from their commodity names to standard commodity display formats. Can return an error message eg if inconsistent number formats are found.

Though, these amounts may have come from multiple files, so we shouldn't assume they use consistent number formats. Currently we don't enforce that even within a single file, and this function never reports an error.

journalCommodityStyles :: Journal -> Map CommoditySymbol AmountStyle Source #

Get the canonical amount styles for this journal, whether (in order of precedence): set globally in InputOpts, declared by commodity directives, declared by a default commodity (D) directive, or inferred from posting amounts, as a map from symbol to style. Styles from directives are assumed to specify the decimal mark.

journalToCost :: ConversionOp -> 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.

journalAddInferredEquityPostings :: Journal -> Journal Source #

Add inferred equity postings to a Journal using transaction prices.

journalAddPricesFromEquity :: Journal -> Either String Journal Source #

Add inferred transaction prices from equity postings.

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 :: POSIXTime -> Journal -> Journal Source #

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

journalRenumberAccountDeclarations :: Journal -> Journal Source #

Renumber all the account declarations. This is useful to call when finalising or concatenating Journals, to give account declarations a total order across files.

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.

filterJournalRelatedPostings :: Query -> Journal -> Journal Source #

Keep only postings which do not match the query expression, but for which a related posting does. This can leave unbalanced transactions.

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

Within each posting's amount, keep only the parts matching the query, and remove any postings with all amounts removed. 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, and remove any postings with all amounts removed. This can leave the transaction unbalanced.

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

Filter out all parts of this posting's amount which do not match the query, and remove the posting if this removes all amounts.

Mapping

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

Apply a transformation to a journal's transactions.

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

Apply a transformation to a journal's postings.

journalMapPostingAmounts :: (MixedAmount -> MixedAmount) -> Journal -> Journal Source #

Apply a transformation to a journal's posting amounts.

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.

journalLeafAccountNamesDeclared :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives in this journal, which have no children.

journalAccountNames :: Journal -> [AccountName] Source #

Convenience/compatibility alias for journalAccountNamesDeclaredOrImplied.

journalLeafAccountNames :: Journal -> [AccountName] Source #

Sorted unique account names declared or implied in this journal which have no children.

journalAccountTags :: Journal -> AccountName -> [Tag] Source #

Which tags have been declared explicitly for this account, if any ?

journalInheritedAccountTags :: Journal -> AccountName -> [Tag] Source #

Which tags are in effect for this account, including tags inherited from parent accounts ?

journalPayeesDeclared :: Journal -> [Payee] Source #

Sorted unique payees declared by payee directives in this journal.

journalPayeesUsed :: Journal -> [Payee] Source #

Sorted unique payees used by transactions in this journal.

journalPayeesDeclaredOrUsed :: Journal -> [Payee] Source #

Sorted unique payees used in transactions or declared by payee directives in this journal.

journalCommoditiesDeclared :: Journal -> [CommoditySymbol] Source #

Sorted unique commodity symbols declared by commodity directives in this journal.

journalCommodities :: Journal -> Set CommoditySymbol Source #

Sorted unique commodity symbols declared or inferred from this journal.

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

Get an ordered list of AmountStyles from the amounts in this journal which influence canonical amount display styles. See traverseJournalAmounts. journalAmounts :: Journal -> [Amount] journalAmounts = getConst . traverseJournalAmounts (Const . (:[]))

| Apply a transformation to the journal amounts traversed by traverseJournalAmounts. overJournalAmounts :: (Amount -> Amount) -> Journal -> Journal overJournalAmounts f = runIdentity . traverseJournalAmounts (Identity . f)

| A helper that traverses over most amounts in the journal, in particular the ones which influence canonical amount display styles, processing them with the given applicative function.

These include, in the following order:

  • the amount in the final default commodity (D) directive
  • amounts in market price (P) directives (in parse order)
  • posting amounts in transactions (in parse order)

Transaction price amounts, which may be embedded in posting amounts (the aprice field), are left intact but not traversed/processed.

traverseJournalAmounts :: Applicative f => (Amount -> f Amount) -> Journal -> f Journal traverseJournalAmounts f j = recombine $ (traverse . dcamt) f (jparsedefaultcommodity j) * (traverse . pdamt) f (jpricedirectives j) * (traverse . tps . traverse . pamt . amts . traverse) f (jtxns j) where recombine pds txns = j { jpricedirectives = pds, jtxns = txns } -- a bunch of traversals dcamt g pd = (mdc -> case mdc of Nothing -> Nothing Just ((c,stpd{pdamount =amt} ) $ g (pdamount pd) pdamt g pd = (amt -> pd{pdamount =amt}) $ g (pdamount pd) tps g t = (ps -> t {tpostings=ps }) $ g (tpostings t) pamt g p = (amt -> p {pamount =amt}) $ g (pamount p) amts g (Mixed as) = Mixed $ g as

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.

journalDateSpanBothDates :: Journal -> DateSpan Source #

The fully specified date span enclosing the dates (primary and 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 "exclusive end date" of this journal: the day following its latest transaction or posting date, or Nothing if there are none.

journalLastDay :: 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.

journalTransactionsSimilarTo :: Journal -> Query -> Text -> Int -> [(Double, Transaction)] Source #

Find up to N most similar and most recent transactions matching the given transaction description and query. Transactions are listed with their description's similarity score (see compareDescriptions), sorted by highest score and then by date. Only transactions with a similarity score greater than a minimum threshold (currently 0) are returned.

Account types

journalAccountTypes :: Journal -> Map AccountName AccountType Source #

Build a map of all known account types, explicitly declared or inferred from the account's parent or name.

journalAddAccountTypes :: Journal -> Journal Source #

Add a map of all known account types to the journal.

journalPostingsAddAccountTags :: Journal -> Journal Source #

To all postings in the journal, add any tags from their account (including those inherited from parent accounts). If the same tag exists on posting and account, the latter is ignored.

journalConversionAccount :: Journal -> AccountName Source #

The AccountName to use for automatically generated conversion postings.

Misc

canonicalStyleFrom :: [AmountStyle] -> AmountStyle Source #

Given a list of amount styles (assumed to be from parsed amounts in a single commodity), in parse order, choose a canonical style.

journalConcat :: Journal -> Journal -> Journal Source #

Merge two journals into one. Transaction counts are summed, map fields are combined, the second's list fields are appended to the first's, the second's parse state is kept.

journalNumberTransactions :: Journal -> Journal Source #

Number (set the tindex field) this journal's transactions, counting upward from 1.

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 :: Day -> Journal -> Either String Journal Source #

Apply any transaction modifier rules in the journal (adding automated postings to transactions, eg). Or if a modifier rule fails to parse, return the error message. A reference date is provided to help interpret relative dates in transaction modifier queries.

journalApplyAliases :: [AccountAlias] -> Journal -> Either RegexError Journal Source #

Apply some account aliases to all posting account names in the journal, as described by accountNameApplyAliases. This can fail due to a bad replacement pattern in a regular expression alias.

dbgJournalAcctDeclOrder :: String -> Journal -> Journal Source #

Debug log the ordering of a journal's account declarations (at debug level 5+).

Tests

Orphan instances

Semigroup Journal Source # 
Instance details

Show Journal Source # 
Instance details

Default Journal Source # 
Instance details

Methods

def :: Journal #