hledger-lib-1.26.1: A reusable library providing the core functionality of hledger
Safe HaskellNone
LanguageHaskell2010

Hledger.Reports.ReportOptions

Description

Options common to most hledger reports.

Synopsis

Documentation

data ReportOpts Source #

Standard options for customising report filtering and output. Most of these correspond to standard hledger command-line options or query arguments, but not all. Some are used only by certain commands, as noted below.

Constructors

ReportOpts 

Fields

Instances

Instances details
Show ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Default ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: ReportOpts #

HasReportOptsNoUpdate ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportOpts ReportOpts Source #

accountlistmode :: Lens' ReportOpts AccountListMode Source #

average :: Lens' ReportOpts Bool Source #

balanceaccum :: Lens' ReportOpts BalanceAccumulation Source #

balancecalc :: Lens' ReportOpts BalanceCalculation Source #

budgetpat :: Lens' ReportOpts (Maybe Text) Source #

color__ :: Lens' ReportOpts Bool Source #

conversionop :: Lens' ReportOpts (Maybe ConversionOp) Source #

date2NoUpdate :: Lens' ReportOpts Bool Source #

declared :: Lens' ReportOpts Bool Source #

depthNoUpdate :: Lens' ReportOpts (Maybe Int) Source #

drop__ :: Lens' ReportOpts Int Source #

empty__ :: Lens' ReportOpts Bool Source #

format :: Lens' ReportOpts StringFormat Source #

infer_prices :: Lens' ReportOpts Bool Source #

interval :: Lens' ReportOpts Interval Source #

invert :: Lens' ReportOpts Bool Source #

layout :: Lens' ReportOpts Layout Source #

no_elide :: Lens' ReportOpts Bool Source #

no_total :: Lens' ReportOpts Bool Source #

normalbalance :: Lens' ReportOpts (Maybe NormalSign) Source #

percent :: Lens' ReportOpts Bool Source #

periodNoUpdate :: Lens' ReportOpts Period Source #

pretty :: Lens' ReportOpts Bool Source #

querystringNoUpdate :: Lens' ReportOpts [Text] Source #

realNoUpdate :: Lens' ReportOpts Bool Source #

related :: Lens' ReportOpts Bool Source #

row_total :: Lens' ReportOpts Bool Source #

show_costs :: Lens' ReportOpts Bool Source #

sort_amount :: Lens' ReportOpts Bool Source #

statusesNoUpdate :: Lens' ReportOpts [Status] Source #

transpose__ :: Lens' ReportOpts Bool Source #

txn_dates :: Lens' ReportOpts Bool Source #

value :: Lens' ReportOpts (Maybe ValuationType) Source #

HasReportOpts ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportOpts ReportOpts Source #

period :: ReportableLens' ReportOpts Period Source #

statuses :: ReportableLens' ReportOpts [Status] Source #

depth :: ReportableLens' ReportOpts (Maybe Int) Source #

date2 :: ReportableLens' ReportOpts Bool Source #

real :: ReportableLens' ReportOpts Bool Source #

querystring :: ReportableLens' ReportOpts [Text] Source #

class HasReportOptsNoUpdate c where Source #

Lenses for ReportOpts.

Minimal complete definition

reportOptsNoUpdate

Instances

Instances details
HasReportOptsNoUpdate ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportSpec ReportOpts Source #

accountlistmode :: Lens' ReportSpec AccountListMode Source #

average :: Lens' ReportSpec Bool Source #

balanceaccum :: Lens' ReportSpec BalanceAccumulation Source #

balancecalc :: Lens' ReportSpec BalanceCalculation Source #

budgetpat :: Lens' ReportSpec (Maybe Text) Source #

color__ :: Lens' ReportSpec Bool Source #

conversionop :: Lens' ReportSpec (Maybe ConversionOp) Source #

date2NoUpdate :: Lens' ReportSpec Bool Source #

declared :: Lens' ReportSpec Bool Source #

depthNoUpdate :: Lens' ReportSpec (Maybe Int) Source #

drop__ :: Lens' ReportSpec Int Source #

empty__ :: Lens' ReportSpec Bool Source #

format :: Lens' ReportSpec StringFormat Source #

infer_prices :: Lens' ReportSpec Bool Source #

interval :: Lens' ReportSpec Interval Source #

invert :: Lens' ReportSpec Bool Source #

layout :: Lens' ReportSpec Layout Source #

no_elide :: Lens' ReportSpec Bool Source #

no_total :: Lens' ReportSpec Bool Source #

normalbalance :: Lens' ReportSpec (Maybe NormalSign) Source #

percent :: Lens' ReportSpec Bool Source #

periodNoUpdate :: Lens' ReportSpec Period Source #

pretty :: Lens' ReportSpec Bool Source #

querystringNoUpdate :: Lens' ReportSpec [Text] Source #

realNoUpdate :: Lens' ReportSpec Bool Source #

related :: Lens' ReportSpec Bool Source #

row_total :: Lens' ReportSpec Bool Source #

show_costs :: Lens' ReportSpec Bool Source #

sort_amount :: Lens' ReportSpec Bool Source #

statusesNoUpdate :: Lens' ReportSpec [Status] Source #

transpose__ :: Lens' ReportSpec Bool Source #

txn_dates :: Lens' ReportSpec Bool Source #

value :: Lens' ReportSpec (Maybe ValuationType) Source #

HasReportOptsNoUpdate ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportOpts ReportOpts Source #

accountlistmode :: Lens' ReportOpts AccountListMode Source #

average :: Lens' ReportOpts Bool Source #

balanceaccum :: Lens' ReportOpts BalanceAccumulation Source #

balancecalc :: Lens' ReportOpts BalanceCalculation Source #

budgetpat :: Lens' ReportOpts (Maybe Text) Source #

color__ :: Lens' ReportOpts Bool Source #

conversionop :: Lens' ReportOpts (Maybe ConversionOp) Source #

date2NoUpdate :: Lens' ReportOpts Bool Source #

declared :: Lens' ReportOpts Bool Source #

depthNoUpdate :: Lens' ReportOpts (Maybe Int) Source #

drop__ :: Lens' ReportOpts Int Source #

empty__ :: Lens' ReportOpts Bool Source #

format :: Lens' ReportOpts StringFormat Source #

infer_prices :: Lens' ReportOpts Bool Source #

interval :: Lens' ReportOpts Interval Source #

invert :: Lens' ReportOpts Bool Source #

layout :: Lens' ReportOpts Layout Source #

no_elide :: Lens' ReportOpts Bool Source #

no_total :: Lens' ReportOpts Bool Source #

normalbalance :: Lens' ReportOpts (Maybe NormalSign) Source #

percent :: Lens' ReportOpts Bool Source #

periodNoUpdate :: Lens' ReportOpts Period Source #

pretty :: Lens' ReportOpts Bool Source #

querystringNoUpdate :: Lens' ReportOpts [Text] Source #

realNoUpdate :: Lens' ReportOpts Bool Source #

related :: Lens' ReportOpts Bool Source #

row_total :: Lens' ReportOpts Bool Source #

show_costs :: Lens' ReportOpts Bool Source #

sort_amount :: Lens' ReportOpts Bool Source #

statusesNoUpdate :: Lens' ReportOpts [Status] Source #

transpose__ :: Lens' ReportOpts Bool Source #

txn_dates :: Lens' ReportOpts Bool Source #

value :: Lens' ReportOpts (Maybe ValuationType) Source #

class HasReportOptsNoUpdate a => HasReportOpts a where Source #

Special lenses for ReportOpts which also update the Query and QueryOpts in ReportSpec. Note that these are not true lenses, as they have a further restriction on the functor. This will work as a normal lens for all common uses, but since they don't obey the lens laws for some fancy cases, they may fail in some exotic circumstances.

Note that setEither/overEither should only be necessary with querystring and reportOpts: the other lenses should never fail.

Examples:

>>> import Lens.Micro (set)
>>> _rsQuery <$> setEither querystring ["assets"] defreportspec
Right (Acct (RegexpCI "assets"))
>>> _rsQuery <$> setEither querystring ["(assets"] defreportspec
Left "this regular expression could not be compiled: (assets"
>>> _rsQuery $ set querystring ["assets"] defreportspec
Acct (RegexpCI "assets")
>>> _rsQuery $ set querystring ["(assets"] defreportspec
*** Exception: Error: Updating ReportSpec failed: try using overEither instead of over or setEither instead of set
>>> _rsQuery $ set period (MonthPeriod 2021 08) defreportspec
Date DateSpan 2021-08

Minimal complete definition

Nothing

Methods

reportOpts :: ReportableLens' a ReportOpts Source #

period :: ReportableLens' a Period Source #

statuses :: ReportableLens' a [Status] Source #

depth :: ReportableLens' a (Maybe Int) Source #

date2 :: ReportableLens' a Bool Source #

real :: ReportableLens' a Bool Source #

querystring :: ReportableLens' a [Text] Source #

Instances

Instances details
HasReportOpts ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportSpec ReportOpts Source #

period :: ReportableLens' ReportSpec Period Source #

statuses :: ReportableLens' ReportSpec [Status] Source #

depth :: ReportableLens' ReportSpec (Maybe Int) Source #

date2 :: ReportableLens' ReportSpec Bool Source #

real :: ReportableLens' ReportSpec Bool Source #

querystring :: ReportableLens' ReportSpec [Text] Source #

HasReportOpts ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportOpts ReportOpts Source #

period :: ReportableLens' ReportOpts Period Source #

statuses :: ReportableLens' ReportOpts [Status] Source #

depth :: ReportableLens' ReportOpts (Maybe Int) Source #

date2 :: ReportableLens' ReportOpts Bool Source #

real :: ReportableLens' ReportOpts Bool Source #

querystring :: ReportableLens' ReportOpts [Text] Source #

data ReportSpec Source #

The result of successfully parsing a ReportOpts on a particular Day. Any ambiguous dates are completed and Queries are parsed, ensuring that there are no regular expression errors. Values here should be used in preference to re-deriving them from ReportOpts. If you change the query_ in ReportOpts, you should call reportOptsToSpec to regenerate the ReportSpec with the new Query.

Constructors

ReportSpec 

Fields

Instances

Instances details
Show ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Default ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: ReportSpec #

HasReportOptsNoUpdate ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportSpec ReportOpts Source #

accountlistmode :: Lens' ReportSpec AccountListMode Source #

average :: Lens' ReportSpec Bool Source #

balanceaccum :: Lens' ReportSpec BalanceAccumulation Source #

balancecalc :: Lens' ReportSpec BalanceCalculation Source #

budgetpat :: Lens' ReportSpec (Maybe Text) Source #

color__ :: Lens' ReportSpec Bool Source #

conversionop :: Lens' ReportSpec (Maybe ConversionOp) Source #

date2NoUpdate :: Lens' ReportSpec Bool Source #

declared :: Lens' ReportSpec Bool Source #

depthNoUpdate :: Lens' ReportSpec (Maybe Int) Source #

drop__ :: Lens' ReportSpec Int Source #

empty__ :: Lens' ReportSpec Bool Source #

format :: Lens' ReportSpec StringFormat Source #

infer_prices :: Lens' ReportSpec Bool Source #

interval :: Lens' ReportSpec Interval Source #

invert :: Lens' ReportSpec Bool Source #

layout :: Lens' ReportSpec Layout Source #

no_elide :: Lens' ReportSpec Bool Source #

no_total :: Lens' ReportSpec Bool Source #

normalbalance :: Lens' ReportSpec (Maybe NormalSign) Source #

percent :: Lens' ReportSpec Bool Source #

periodNoUpdate :: Lens' ReportSpec Period Source #

pretty :: Lens' ReportSpec Bool Source #

querystringNoUpdate :: Lens' ReportSpec [Text] Source #

realNoUpdate :: Lens' ReportSpec Bool Source #

related :: Lens' ReportSpec Bool Source #

row_total :: Lens' ReportSpec Bool Source #

show_costs :: Lens' ReportSpec Bool Source #

sort_amount :: Lens' ReportSpec Bool Source #

statusesNoUpdate :: Lens' ReportSpec [Status] Source #

transpose__ :: Lens' ReportSpec Bool Source #

txn_dates :: Lens' ReportSpec Bool Source #

value :: Lens' ReportSpec (Maybe ValuationType) Source #

HasReportOpts ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportSpec ReportOpts Source #

period :: ReportableLens' ReportSpec Period Source #

statuses :: ReportableLens' ReportSpec [Status] Source #

depth :: ReportableLens' ReportSpec (Maybe Int) Source #

date2 :: ReportableLens' ReportSpec Bool Source #

real :: ReportableLens' ReportSpec Bool Source #

querystring :: ReportableLens' ReportSpec [Text] Source #

HasReportSpec ReportSpec Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t Source #

Apply a function over a lens, but report on failure.

setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t Source #

Set a field using a lens, but report on failure.

data BalanceCalculation Source #

What to calculate for each cell in a balance report. "Balance report types -> Calculation type" in the hledger manual.

Constructors

CalcChange

Sum of posting amounts in the period.

CalcBudget

Sum of posting amounts and the goal for the period.

CalcValueChange

Change from previous period's historical end value to this period's historical end value.

CalcGain

Change from previous period's gain, i.e. valuation minus cost basis.

data BalanceAccumulation Source #

How to accumulate calculated values across periods (columns) in a balance report. "Balance report types -> Accumulation type" in the hledger manual.

Constructors

PerPeriod

No accumulation. Eg, shows the change of balance in each period.

Cumulative

Accumulate changes across periods, starting from zero at report start.

Historical

Accumulate changes across periods, including any from before report start. Eg, shows the historical end balance of each period.

data AccountListMode Source #

Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?

Constructors

ALFlat 
ALTree 

data ValuationType Source #

What kind of value conversion should be done on amounts ? CLI: --value=then|end|now|DATE[,COMM]

Constructors

AtThen (Maybe CommoditySymbol)

convert to default or given valuation commodity, using market prices at each posting's date

AtEnd (Maybe CommoditySymbol)

convert to default or given valuation commodity, using market prices at period end(s)

AtNow (Maybe CommoditySymbol)

convert to default or given valuation commodity, using current market prices

AtDate Day (Maybe CommoditySymbol)

convert to default or given valuation commodity, using market prices on some date

Instances

Instances details
Eq ValuationType Source # 
Instance details

Defined in Hledger.Data.Valuation

Show ValuationType Source # 
Instance details

Defined in Hledger.Data.Valuation

data Layout Source #

Instances

Instances details
Eq Layout Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

(==) :: Layout -> Layout -> Bool #

(/=) :: Layout -> Layout -> Bool #

Show Layout Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

rawOptsToReportOpts :: Day -> RawOpts -> ReportOpts Source #

Generate a ReportOpts from raw command-line input, given a day. This will fail with a usage error if it is passed - an invalid --format argument, - an invalid --value argument, - if --valuechange is called with a valuation type other than -V/--value=end. - an invalid --pretty argument,

setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec Source #

Set the default ConversionOp.

reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec Source #

Generate a ReportSpec from a set of ReportOpts on a given day.

updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec Source #

Update the ReportOpts and the fields derived from it in a ReportSpec, or return an error message if there is a problem such as missing or unparseable options data. This is the safe way to change a ReportSpec, ensuring that all fields (_rsQuery, _rsReportOpts, querystring_, etc.) are in sync.

updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec Source #

Like updateReportSpec, but takes a ReportOpts-modifying function.

rawOptsToReportSpec :: Day -> RawOpts -> Either String ReportSpec Source #

Generate a ReportSpec from RawOpts and a provided day, or return an error string if there are regular expression errors.

tree_ :: ReportOpts -> Bool Source #

Legacy-compatible convenience aliases for accountlistmode_.

reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts Source #

Add/remove this status from the status list. Used by hledger-ui.

simplifyStatuses :: Ord a => [a] -> [a] Source #

Reduce a list of statuses to just one of each status, and if all statuses are present return the empty list.

whichDate :: ReportOpts -> WhichDate Source #

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

journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal Source #

Convert a Journal's amounts to cost and/or to value (see journalApplyValuationFromOpts), and filter by the ReportSpec Query.

We make sure to first filter by amt: and cur: terms, then value the Journal, then filter by the remaining terms.

journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal Source #

Convert this journal's postings' amounts to cost and/or to value, if specified by options (-B--cost-V-X--value etc.). Strip prices if not needed. This should be the main stop for performing costing and valuation. The exception is whenever you need to perform valuation _after_ summing up amounts, as in a historical balance report with --value=end. valuationAfterSum will check for this condition.

journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal Source #

Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.

mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount Source #

Select the Account valuation functions required for performing valuation after summing amounts. Used in MultiBalanceReport to value historical and similar reports.

valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol) Source #

If the ReportOpts specify that we are performing valuation after summing amounts, return Just of the commodity symbol we're converting to, Just Nothing for the default, and otherwise return Nothing. Used for example with historical reports with --value=end.

intervalFromRawOpts :: RawOpts -> Interval Source #

Get the report interval, if any, specified by the last of -p/--period, -D--daily, -W--weekly, -M/--monthly etc. options. An interval from --period counts only if it is explicitly defined.

queryFromFlags :: ReportOpts -> Query Source #

Convert report options to a query, ignoring any non-flag command line arguments.

transactionDateFn :: ReportOpts -> Transaction -> Day Source #

Select the Transaction date accessor based on --date2.

postingDateFn :: ReportOpts -> Posting -> Day Source #

Select the Posting date accessor based on --date2.

reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan]) Source #

The effective report span is the start and end dates specified by options or queries, or otherwise the earliest and latest transaction or posting dates in the journal. If no dates are specified by options/queries and the journal is empty, returns the null date span. Also return the intervals if they are requested.

reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan]) Source #

Like reportSpan, but uses both primary and secondary dates when calculating the span.

reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text Source #

Make a name for the given period in a multiperiod report, given the type of balance being reported and the full set of report periods. This will be used as a column heading (or row heading, in a register summary report). We try to pick a useful name as follows:

  • ending-balance reports: the period's end date
  • balance change reports where the periods are months and all in the same year: the short month name in the current locale
  • all other balance change reports: a description of the datespan, abbreviated to compact form if possible (see showDateSpan).