hledger-lib-0.21.2: Core data types, parsers and utilities for the hledger accounting tool.

Safe HaskellNone

Hledger.Reports

Contents

Description

Generate several common kinds of report from a journal, as "*Report" - simple intermediate data structures intended to be easily rendered as text, html, json, csv etc. by hledger commands, hamlet templates, javascript, or whatever. This is under Hledger.Cli since it depends on the command-line options, should move to hledger-lib later.

Synopsis

Documentation

data ReportOpts Source

Standard options for customising report filtering and output, corresponding to hledger's command-line options and query language arguments. Used in hledger-lib and above.

dateSpanFromOpts :: Day -> ReportOpts -> DateSpanSource

Figure out the date span we should report on, based on any beginendperiod options provided. A period option will cause begin and end options to be ignored.

intervalFromOpts :: ReportOpts -> IntervalSource

Figure out the reporting interval, if any, specified by the options. --period overrides --daily overrides --weekly overrides --monthly etc.

clearedValueFromOpts :: ReportOpts -> Maybe BoolSource

Get a maybe boolean representing the last cleared/uncleared option if any.

whichDateFromOpts :: ReportOpts -> WhichDateSource

Report which date we will report on based on --date2.

journalSelectingAmountFromOpts :: ReportOpts -> Journal -> JournalSource

Convert this journal's postings' amounts to the cost basis amounts if specified by options.

queryFromOpts :: Day -> ReportOpts -> QuerySource

Convert report options and arguments to a query.

queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt]Source

Convert report options and arguments to query options.

Entries report

type EntriesReport = [EntriesReportItem]Source

A journal entries report is a list of whole transactions as originally entered in the journal (mostly). Used by eg hledger's print command and hledger-web's journal entries view.

entriesReport :: ReportOpts -> Query -> Journal -> EntriesReportSource

Select transactions for an entries report.

Postings report

type PostingsReport = (String, [PostingsReportItem])Source

A postings report is a list of postings with a running total, a label for the total field, and a little extra transaction info to help with rendering.

postingsReport :: ReportOpts -> Query -> Journal -> PostingsReportSource

Select postings from the journal and add running balance and other information to make a postings report. Used by eg hledger's register command.

mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Posting -> MixedAmount -> PostingsReportItemSource

Generate one postings report line item, containing the posting, the current running balance, and optionally the posting date and/or the transaction description.

Transactions report

type TransactionsReport = (String, [TransactionsReportItem])Source

A transactions report includes a list of transactions (posting-filtered and unfiltered variants), a running balance, and some other information helpful for rendering a register view (a flag indicating multiple other accounts and a display string describing them) with or without a notion of current account(s).

triDate :: (Transaction, t, t1, t2, t3, t4) -> DaySource

triBalance :: (t, t1, t2, t3, t4, t5) -> t5Source

triSimpleBalance :: (t, t1, t2, t3, t4, MixedAmount) -> [Char]Source

journalTransactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReportSource

Select transactions from the whole journal for a transactions report, with no "current" account. The end result is similar to postingsReport except it uses queries and transaction-based report items and the items are most recent first. Used by eg hledger-web's journal view.

accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> TransactionsReportSource

Select transactions within one or more "current" accounts, and make a transactions report relative to those account(s). This means:

  1. it shows transactions from the point of view of the current account(s). The transaction amount is the amount posted to the current account(s). The other accounts' names are provided.
  2. With no transaction filtering in effect other than a start date, it shows the accurate historical running balance for the current account(s). Otherwise it shows a running total starting at 0.

Currently, reporting intervals are not supported, and report items are most recent first. Used by eg hledger-web's account register view.

Accounts report

type AccountsReport = ([AccountsReportItem], MixedAmount)Source

An accounts report is a list of account names (full and short variants) with their balances, appropriate indentation for rendering as a hierarchy, and grand total.

accountsReport :: ReportOpts -> Query -> Journal -> AccountsReportSource

Select accounts, and get their balances at the end of the selected period, and misc. display information, for an accounts report.

Other reports

accountBalanceHistory :: ReportOpts -> Journal -> Account -> [(Day, MixedAmount)]Source

Get the historical running inclusive balance of a particular account, from earliest to latest posting date. XXX Accounts should know the Ledger & Journal they came from

Tests