Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hledger.Reports.ReportTypes
Description
New common report types, used by the BudgetReport for now, perhaps all reports later.
Synopsis
- data PeriodicReport a b = PeriodicReport {
- prDates :: [DateSpan]
- prRows :: [PeriodicReportRow a b]
- prTotals :: PeriodicReportRow () b
- data PeriodicReportRow a b = PeriodicReportRow {
- prrName :: a
- prrAmounts :: [b]
- prrTotal :: b
- prrAverage :: b
- type Percentage = Decimal
- type Change = MixedAmount
- type Balance = MixedAmount
- type Total = MixedAmount
- type Average = MixedAmount
- periodicReportSpan :: PeriodicReport a b -> DateSpan
- prMapName :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c
- prMapMaybeName :: (a -> Maybe b) -> PeriodicReport a c -> PeriodicReport b c
- data CompoundPeriodicReport a b = CompoundPeriodicReport {
- cbrTitle :: Text
- cbrDates :: [DateSpan]
- cbrSubreports :: [(Text, PeriodicReport a b, Bool)]
- cbrTotals :: PeriodicReportRow () b
- data CBCSubreportSpec a = CBCSubreportSpec {}
- data DisplayName = DisplayName {
- displayFull :: AccountName
- displayName :: AccountName
- displayIndent :: NumberOfIndents
- flatDisplayName :: AccountName -> DisplayName
- treeDisplayName :: AccountName -> DisplayName
- prrShowDebug :: PeriodicReportRow DisplayName MixedAmount -> String
- prrFullName :: PeriodicReportRow DisplayName a -> AccountName
- prrDisplayName :: PeriodicReportRow DisplayName a -> AccountName
- prrIndent :: PeriodicReportRow DisplayName a -> Int
- prrAdd :: Semigroup b => PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b
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:
- a list of each column's period (date span)
- 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
BalanceAccumulation
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
- the column totals, and the overall grand total (or zero for cumulative/historical reports) and grand average.
Constructors
PeriodicReport | |
Fields
|
Instances
data PeriodicReportRow a b Source #
Constructors
PeriodicReportRow | |
Fields
|
Instances
Bifunctor PeriodicReportRow Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods bimap :: (a -> b) -> (c -> d) -> PeriodicReportRow a c -> PeriodicReportRow b d # first :: (a -> b) -> PeriodicReportRow a c -> PeriodicReportRow b c # second :: (b -> c) -> PeriodicReportRow a b -> PeriodicReportRow a c # | |||||
Functor (PeriodicReportRow a) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods fmap :: (a0 -> b) -> PeriodicReportRow a a0 -> PeriodicReportRow a b # (<$) :: a0 -> PeriodicReportRow a b -> PeriodicReportRow a a0 # | |||||
(ToJSON b, ToJSON a) => ToJSON (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods toJSON :: PeriodicReportRow a b -> Value # toEncoding :: PeriodicReportRow a b -> Encoding # toJSONList :: [PeriodicReportRow a b] -> Value # toEncodingList :: [PeriodicReportRow a b] -> Encoding # omitField :: PeriodicReportRow a b -> Bool # | |||||
Semigroup b => Semigroup (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods (<>) :: PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b # sconcat :: NonEmpty (PeriodicReportRow a b) -> PeriodicReportRow a b # stimes :: Integral b0 => b0 -> PeriodicReportRow a b -> PeriodicReportRow a b # | |||||
Generic (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Associated Types
Methods from :: PeriodicReportRow a b -> Rep (PeriodicReportRow a b) x # to :: Rep (PeriodicReportRow a b) x -> PeriodicReportRow a b # | |||||
(Show a, Show b) => Show (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods showsPrec :: Int -> PeriodicReportRow a b -> ShowS # show :: PeriodicReportRow a b -> String # showList :: [PeriodicReportRow a b] -> ShowS # | |||||
HasAmounts b => HasAmounts (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PeriodicReportRow a b -> PeriodicReportRow a b Source # | |||||
type Rep (PeriodicReportRow a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes type Rep (PeriodicReportRow a b) = D1 ('MetaData "PeriodicReportRow" "Hledger.Reports.ReportTypes" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" '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 Percentage = Decimal Source #
Arguments
= MixedAmount | A change in balance during a certain period. |
Arguments
= MixedAmount | An ending balance as of some date. |
Arguments
= MixedAmount | The sum of |
Arguments
= MixedAmount | The average of |
periodicReportSpan :: PeriodicReport a b -> DateSpan Source #
Figure out the overall date span of a PeriodicReport
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.
Constructors
CompoundPeriodicReport | |
Fields
|
Instances
Functor (CompoundPeriodicReport a) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods fmap :: (a0 -> b) -> CompoundPeriodicReport a a0 -> CompoundPeriodicReport a b # (<$) :: a0 -> CompoundPeriodicReport a b -> CompoundPeriodicReport a a0 # | |||||
(ToJSON b, ToJSON a) => ToJSON (CompoundPeriodicReport a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods toJSON :: CompoundPeriodicReport a b -> Value # toEncoding :: CompoundPeriodicReport a b -> Encoding # toJSONList :: [CompoundPeriodicReport a b] -> Value # toEncodingList :: [CompoundPeriodicReport a b] -> Encoding # omitField :: CompoundPeriodicReport a b -> Bool # | |||||
Generic (CompoundPeriodicReport a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Associated Types
Methods from :: CompoundPeriodicReport a b -> Rep (CompoundPeriodicReport a b) x # to :: Rep (CompoundPeriodicReport a b) x -> CompoundPeriodicReport a b # | |||||
(Show a, Show b) => Show (CompoundPeriodicReport a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods showsPrec :: Int -> CompoundPeriodicReport a b -> ShowS # show :: CompoundPeriodicReport a b -> String # showList :: [CompoundPeriodicReport a b] -> ShowS # | |||||
HasAmounts b => HasAmounts (CompoundPeriodicReport a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> CompoundPeriodicReport a b -> CompoundPeriodicReport a b Source # | |||||
type Rep (CompoundPeriodicReport a b) Source # | |||||
Defined in Hledger.Reports.ReportTypes type Rep (CompoundPeriodicReport a b) = D1 ('MetaData "CompoundPeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "CompoundPeriodicReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cbrTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cbrDates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DateSpan])) :*: (S1 ('MetaSel ('Just "cbrSubreports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, PeriodicReport a b, Bool)]) :*: S1 ('MetaSel ('Just "cbrTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PeriodicReportRow () b))))) |
data CBCSubreportSpec a Source #
Description of one subreport within a compound balance report. Part of a CompoundBalanceCommandSpec, but also used in hledger-lib.
Constructors
CBCSubreportSpec | |
Fields
|
data DisplayName Source #
A full name, display name, and indent level for an account.
Constructors
DisplayName | |
Fields
|
Instances
ToJSON DisplayName Source # | |
Defined in Hledger.Reports.ReportTypes Methods toJSON :: DisplayName -> Value # toEncoding :: DisplayName -> Encoding # toJSONList :: [DisplayName] -> Value # toEncodingList :: [DisplayName] -> Encoding # omitField :: DisplayName -> Bool # | |
Show DisplayName Source # | |
Defined in Hledger.Reports.ReportTypes Methods showsPrec :: Int -> DisplayName -> ShowS # show :: DisplayName -> String # showList :: [DisplayName] -> ShowS # | |
Eq DisplayName Source # | |
Defined in Hledger.Reports.ReportTypes | |
Ord DisplayName Source # | |
Defined in Hledger.Reports.ReportTypes Methods compare :: DisplayName -> DisplayName -> Ordering # (<) :: DisplayName -> DisplayName -> Bool # (<=) :: DisplayName -> DisplayName -> Bool # (>) :: DisplayName -> DisplayName -> Bool # (>=) :: DisplayName -> DisplayName -> Bool # max :: DisplayName -> DisplayName -> DisplayName # min :: DisplayName -> DisplayName -> DisplayName # |
flatDisplayName :: AccountName -> DisplayName Source #
Construct a display name for a list report, where full names are shown unindented.
treeDisplayName :: AccountName -> DisplayName Source #
Construct a display name for a tree report, where leaf names (possibly prefixed by boring parents) are shown indented).
prrFullName :: PeriodicReportRow DisplayName a -> AccountName Source #
Get the full canonical account name from a PeriodicReportRow containing a DisplayName.
prrDisplayName :: PeriodicReportRow DisplayName a -> AccountName Source #
Get the account display name from a PeriodicReportRow containing a DisplayName.
prrIndent :: PeriodicReportRow DisplayName a -> Int Source #
Get the indent level from a PeriodicReportRow containing a DisplayName.
prrAdd :: Semigroup b => PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b Source #
Add two PeriodicReportRows
, preserving the name of the first.