hledger-lib-1.19: A reusable library providing the core functionality of hledger

Safe HaskellNone
LanguageHaskell2010

Hledger.Reports.ReportTypes

Description

New common report types, used by the BudgetReport for now, perhaps all reports later.

Synopsis

Documentation

data PeriodicReport a b Source #

A periodic report is a generic tabular report, where each row corresponds to some label (usually an account name) and each column to a date period. The column periods are usually consecutive subperiods formed by splitting the overall report period by some report interval (daily, weekly, etc.). It has:

  1. a list of each column's period (date span)
  2. a list of rows, each containing:
  • an account label
  • the account's depth
  • A list of amounts, one for each column. Depending on the value type, these can represent balance changes, ending balances, budget performance, etc. (for example, see BalanceType and Hledger.Cli.Commands.Balance).
  • the total of the row's amounts for a periodic report, or zero for cumulative/historical reports (since summing end balances generally doesn't make sense).
  • the average of the row's amounts
  1. the column totals, and the overall grand total (or zero for cumulative/historical reports) and grand average.
Instances
Functor (PeriodicReport a) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

fmap :: (a0 -> b) -> PeriodicReport a a0 -> PeriodicReport a b #

(<$) :: a0 -> PeriodicReport a b -> PeriodicReport a a0 #

(Show a, Show b) => Show (PeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Generic (PeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (PeriodicReport a b) :: Type -> Type #

Methods

from :: PeriodicReport a b -> Rep (PeriodicReport a b) x #

to :: Rep (PeriodicReport a b) x -> PeriodicReport a b #

(ToJSON a, ToJSON b) => ToJSON (PeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReport a b) = D1 (MetaData "PeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.19-9fh02T1n4zjASByyfEEec" False) (C1 (MetaCons "PeriodicReport" PrefixI True) (S1 (MetaSel (Just "prDates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DateSpan]) :*: (S1 (MetaSel (Just "prRows") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PeriodicReportRow a b]) :*: S1 (MetaSel (Just "prTotals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PeriodicReportRow () b)))))

data PeriodicReportRow a b Source #

Constructors

PeriodicReportRow 

Fields

Instances
Functor (PeriodicReportRow a) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

fmap :: (a0 -> b) -> PeriodicReportRow a a0 -> PeriodicReportRow a b #

(<$) :: a0 -> PeriodicReportRow a b -> PeriodicReportRow a a0 #

(Show a, Show b) => Show (PeriodicReportRow a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Generic (PeriodicReportRow a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (PeriodicReportRow a b) :: Type -> Type #

Num b => Semigroup (PeriodicReportRow a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

(ToJSON b, ToJSON a) => ToJSON (PeriodicReportRow a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReportRow a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReportRow a b) = D1 (MetaData "PeriodicReportRow" "Hledger.Reports.ReportTypes" "hledger-lib-1.19-9fh02T1n4zjASByyfEEec" False) (C1 (MetaCons "PeriodicReportRow" PrefixI True) ((S1 (MetaSel (Just "prrName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "prrAmounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [b])) :*: (S1 (MetaSel (Just "prrTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b) :*: S1 (MetaSel (Just "prrAverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))))

type Change Source #

Arguments

 = MixedAmount

A change in balance during a certain period.

type Balance Source #

Arguments

 = MixedAmount

An ending balance as of some date.

type Total Source #

Arguments

 = MixedAmount

The sum of Changes in a report or a report row. Does not make sense for Balances.

type Average Source #

Arguments

 = MixedAmount

The average of Changes or Balances in a report or report row.

periodicReportSpan :: PeriodicReport a b -> DateSpan Source #

Figure out the overall date span of a PeridicReport

prNormaliseSign :: Num b => NormalSign -> PeriodicReport a b -> PeriodicReport a b Source #

Given a PeriodicReport and its normal balance sign, if it is known to be normally negative, convert it to normally positive.

prMapName :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c Source #

Map a function over the row names.

prMapMaybeName :: (a -> Maybe b) -> PeriodicReport a c -> PeriodicReport b c Source #

Map a function over the row names, possibly discarding some.

data CompoundPeriodicReport a b Source #

A compound balance report has:

  • an overall title
  • the period (date span) of each column
  • one or more named, normal-positive multi balance reports, with columns corresponding to the above, and a flag indicating whether they increased or decreased the overall totals
  • a list of overall totals for each column, and their grand total and average

It is used in compound balance report commands like balancesheet, cashflow and incomestatement.

Instances
(Show a, Show b) => Show (CompoundPeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Generic (CompoundPeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (CompoundPeriodicReport a b) :: Type -> Type #

(ToJSON b, ToJSON a) => ToJSON (CompoundPeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (CompoundPeriodicReport a b) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (CompoundPeriodicReport a b) = D1 (MetaData "CompoundPeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.19-9fh02T1n4zjASByyfEEec" False) (C1 (MetaCons "CompoundPeriodicReport" PrefixI True) ((S1 (MetaSel (Just "cbrTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "cbrDates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DateSpan])) :*: (S1 (MetaSel (Just "cbrSubreports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, PeriodicReport a b, Bool)]) :*: S1 (MetaSel (Just "cbrTotals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PeriodicReportRow () b)))))

data CBCSubreportSpec Source #

Description of one subreport within a compound balance report. Part of a CompoundBalanceCommandSpec, but also used in hledger-lib.

flatDisplayName :: AccountName -> DisplayName Source #

Construct a flat display name, where the full name is also displayed at depth 1

treeDisplayName :: AccountName -> DisplayName Source #

Construct a tree display name, where only the leaf is displayed at its given depth

prrFullName :: PeriodicReportRow DisplayName a -> AccountName Source #

Get the full, canonical, name of a PeriodicReportRow tagged by a DisplayName.

prrDisplayName :: PeriodicReportRow DisplayName a -> AccountName Source #

Get the display name of a PeriodicReportRow tagged by a DisplayName.

prrDepth :: PeriodicReportRow DisplayName a -> Int Source #

Get the display depth of a PeriodicReportRow tagged by a DisplayName.