hledger-lib-0.22.1: 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.

Synopsis

Report options

 

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.

data BalanceType Source

Which balance is being shown in a multi-column balance report.

Constructors

PeriodBalance

The change of balance in each period.

CumulativeBalance

The accumulated balance at each period's end, starting from zero at the report start date.

HistoricalBalance

The historical balance at each period's end, starting from the account balances at the report start date.

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.

reportSpans :: ReportOpts -> Query -> Journal -> (DateSpan, [DateSpan])Source

Calculate the overall span and per-period date spans for a report based on command-line options, the parsed search query, and the journal data. If a reporting interval is specified, the report span will be enlarged to include a whole number of report periods. Reports will sometimes trim these spans further when appropriate.

Entries report

 

type EntriesReport = [EntriesReportItem]Source

A journal entries report is a list of whole transactions as originally entered in the journal (mostly). This is 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. This is used eg for the register command.

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). Two kinds of report use this data structure, see journalTransactionsReport and accountTransactionsReport below for detais.

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. This is similar to a postingsReport except with transaction-based report items which are ordered most recent first. This is 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.

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

Balance reports

These are used for the various modes of the balance command (see Hledger.Cli.Balance).

type BalanceReport = ([BalanceReportItem], MixedAmount)Source

A list of account names plus rendering info, along with their balances as of the end of the reporting period, and the grand total. Used for the balance command's single-column mode.

type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount)Source

  • Full account name,
  • short account name for display (the leaf name, prefixed by any boring parents immediately above),
  • how many steps to indent this account (the 0-based account depth excluding boring parents, or 0 with --flat),
  • account balance (including subaccounts (XXX unless --flat)).

balanceReport :: ReportOpts -> Query -> Journal -> BalanceReportSource

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

newtype MultiBalanceReport Source

A multi(column) balance report is a list of accounts, each with a list of balances corresponding to the report's column periods. The balances' meaning depends on the type of balance report (see BalanceType and Hledger.Cli.Balance). Also included are the overall total for each period, the date span for each period, and some additional rendering info for the accounts.

  • The date span for each report column,
  • line items (one per account),
  • the final total for each report column.

type MultiBalanceReportItem = (RenderableAccountName, [MixedAmount])Source

  • The account name with rendering hints,
  • the account's balance (per-period balance, cumulative ending balance, or historical ending balance) in each of the report's periods.

type RenderableAccountName = (AccountName, AccountName, Int)Source

  • Full account name,
  • ledger-style short account name (the leaf name, prefixed by any boring parents immediately above),
  • indentation steps to use when rendering a ledger-style account tree (the 0-based depth of this account excluding boring parents; or with --flat, 0)

periodBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReportSource

Select accounts and get their period balance (change of balance) in each period, plus misc. display information, for a period balance report.

cumulativeOrHistoricalBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReportSource

Select accounts and get their ending balance in each period, plus account name display information, for a cumulative or historical balance 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