hledger-0.8: A command-line (or curses or web-based) double-entry accounting tool.Source codeContentsIndex
Ledger.Journal
Description
A Journal is a parsed ledger file, containing Transactions. It can be filtered and massaged in various ways, then "crunched" to form a Ledger.
Synopsis
nulljournal :: Journal
addTransaction :: Transaction -> Journal -> Journal
addModifierTransaction :: ModifierTransaction -> Journal -> Journal
addPeriodicTransaction :: PeriodicTransaction -> Journal -> Journal
addHistoricalPrice :: HistoricalPrice -> Journal -> Journal
addTimeLogEntry :: TimeLogEntry -> Journal -> Journal
journalPostings :: Journal -> [Posting]
journalAccountNamesUsed :: Journal -> [AccountName]
journalAccountNames :: Journal -> [AccountName]
journalAccountNameTree :: Journal -> Tree AccountName
filterJournalTransactions :: FilterSpec -> Journal -> Journal
filterJournalPostings :: FilterSpec -> Journal -> Journal
filterJournalTransactionsByDescription :: [String] -> Journal -> Journal
filterJournalTransactionsByDate :: DateSpan -> Journal -> Journal
filterJournalTransactionsByClearedStatus :: Maybe Bool -> Journal -> Journal
filterJournalPostingsByClearedStatus :: Maybe Bool -> Journal -> Journal
filterJournalPostingsByRealness :: Bool -> Journal -> Journal
filterJournalPostingsByEmpty :: Bool -> Journal -> Journal
filterJournalTransactionsByDepth :: Maybe Int -> Journal -> Journal
filterJournalPostingsByDepth :: Maybe Int -> Journal -> Journal
filterJournalTransactionsByAccount :: [String] -> Journal -> Journal
filterJournalPostingsByAccount :: [String] -> Journal -> Journal
journalSelectingDate :: WhichDate -> Journal -> Journal
canonicaliseAmounts :: Bool -> Journal -> Journal
journalAmounts :: Journal -> [MixedAmount]
journalCommodities :: Journal -> [Commodity]
journalPrecisions :: Journal -> [Int]
journalConvertTimeLog :: LocalTime -> Journal -> Journal
journalDateSpan :: Journal -> DateSpan
matchpats :: [String] -> String -> Bool
crunchJournal :: Journal -> (Tree AccountName, Map AccountName Account)
groupPostings :: [Posting] -> (Tree AccountName, AccountName -> [Posting], AccountName -> MixedAmount, AccountName -> MixedAmount)
calculateBalances :: Tree AccountName -> (AccountName -> [Posting]) -> Tree (AccountName, (MixedAmount, MixedAmount))
postingsByAccount :: [Posting] -> Map AccountName [Posting]
Documentation
nulljournal :: JournalSource
addTransaction :: Transaction -> Journal -> JournalSource
addModifierTransaction :: ModifierTransaction -> Journal -> JournalSource
addPeriodicTransaction :: PeriodicTransaction -> Journal -> JournalSource
addHistoricalPrice :: HistoricalPrice -> Journal -> JournalSource
addTimeLogEntry :: TimeLogEntry -> Journal -> JournalSource
journalPostings :: Journal -> [Posting]Source
journalAccountNamesUsed :: Journal -> [AccountName]Source
journalAccountNames :: Journal -> [AccountName]Source
journalAccountNameTree :: Journal -> Tree AccountNameSource
filterJournalTransactions :: FilterSpec -> Journal -> JournalSource
Keep only transactions we are interested in, as described by the filter specification. May also massage the data a little.
filterJournalPostings :: FilterSpec -> Journal -> JournalSource
Keep only postings we are interested in, as described by the filter specification. May also massage the data a little. This can leave unbalanced transactions.
filterJournalTransactionsByDescription :: [String] -> Journal -> JournalSource
Keep only ledger transactions whose description matches the description patterns.
filterJournalTransactionsByDate :: DateSpan -> Journal -> JournalSource
Keep only ledger transactions which fall between begin and end dates. We include transactions on the begin date and exclude transactions on the end date, like ledger. An empty date string means no restriction.
filterJournalTransactionsByClearedStatus :: Maybe Bool -> Journal -> JournalSource
Keep only ledger transactions which have the requested cleared/uncleared status, if there is one.
filterJournalPostingsByClearedStatus :: Maybe Bool -> Journal -> JournalSource
Keep only postings which have the requested cleared/uncleared status, if there is one.
filterJournalPostingsByRealness :: Bool -> Journal -> JournalSource
Strip out any virtual postings, if the flag is true, otherwise do no filtering.
filterJournalPostingsByEmpty :: Bool -> Journal -> JournalSource
Strip out any postings with zero amount, unless the flag is true.
filterJournalTransactionsByDepth :: Maybe Int -> Journal -> JournalSource
Keep only transactions which affect accounts deeper than the specified depth.
filterJournalPostingsByDepth :: Maybe Int -> Journal -> JournalSource
Strip out any postings to accounts deeper than the specified depth (and any ledger transactions which have no postings as a result).
filterJournalTransactionsByAccount :: [String] -> Journal -> JournalSource
Keep only transactions which affect accounts matched by the account patterns.
filterJournalPostingsByAccount :: [String] -> Journal -> JournalSource
Keep only postings which affect accounts matched by the account patterns. This can leave transactions unbalanced.
journalSelectingDate :: WhichDate -> Journal -> JournalSource
Convert this journal's transactions' primary date to either the actual or effective date.
canonicaliseAmounts :: Bool -> Journal -> JournalSource
Convert all the journal's amounts to their canonical display settings. Ie, in each commodity, amounts will use the display settings of the first amount detected, and the greatest precision of the amounts detected. Also, missing unit prices are added if known from the price history. Also, amounts are converted to cost basis if that flag is active. XXX refactor
journalAmounts :: Journal -> [MixedAmount]Source
Get just the amounts from a ledger, in the order parsed.
journalCommodities :: Journal -> [Commodity]Source
Get just the ammount commodities from a ledger, in the order parsed.
journalPrecisions :: Journal -> [Int]Source
Get just the amount precisions from a ledger, in the order parsed.
journalConvertTimeLog :: LocalTime -> Journal -> JournalSource
Close any open timelog sessions using the provided current time.
journalDateSpan :: Journal -> DateSpanSource
The (fully specified) date span containing all the raw ledger's transactions, or DateSpan Nothing Nothing if there are none.
matchpats :: [String] -> String -> BoolSource
Check if a set of ledger account/description patterns matches the given account name or entry description. Patterns are case-insensitive regular expression strings; those beginning with - are anti-patterns.
crunchJournal :: Journal -> (Tree AccountName, Map AccountName Account)Source
Calculate the account tree and account balances from a journal's postings, and return the results for efficient lookup.
groupPostings :: [Posting] -> (Tree AccountName, AccountName -> [Posting], AccountName -> MixedAmount, AccountName -> MixedAmount)Source
Given a list of postings, return an account name tree and three query functions that fetch postings, balance, and subaccount-including balance by account name. This factors out common logic from cacheLedger and summarisePostingsInDateSpan.
calculateBalances :: Tree AccountName -> (AccountName -> [Posting]) -> Tree (AccountName, (MixedAmount, MixedAmount))Source
Add subaccount-excluding and subaccount-including balances to a tree of account names somewhat efficiently, given a function that looks up transactions by account name.
postingsByAccount :: [Posting] -> Map AccountName [Posting]Source
Convert a list of postings to a map from account name to that account's postings.
Produced by Haddock version 2.6.0