Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hledger.Reports.ReportOptions
Description
Options common to most hledger reports.
Synopsis
- data ReportOpts = ReportOpts {
- period_ :: Period
- interval_ :: Interval
- statuses_ :: [Status]
- conversionop_ :: Maybe ConversionOp
- value_ :: Maybe ValuationType
- infer_prices_ :: Bool
- depth_ :: DepthSpec
- date2_ :: Bool
- empty_ :: Bool
- no_elide_ :: Bool
- real_ :: Bool
- format_ :: StringFormat
- balance_base_url_ :: Maybe Text
- pretty_ :: Bool
- querystring_ :: [Text]
- average_ :: Bool
- related_ :: Bool
- sortspec_ :: SortSpec
- txn_dates_ :: Bool
- balancecalc_ :: BalanceCalculation
- balanceaccum_ :: BalanceAccumulation
- budgetpat_ :: Maybe Text
- accountlistmode_ :: AccountListMode
- drop_ :: Int
- declared_ :: Bool
- row_total_ :: Bool
- no_total_ :: Bool
- summary_only_ :: Bool
- show_costs_ :: Bool
- sort_amount_ :: Bool
- percent_ :: Bool
- invert_ :: Bool
- normalbalance_ :: Maybe NormalSign
- color_ :: Bool
- transpose_ :: Bool
- layout_ :: Layout
- class HasReportOptsNoUpdate c where
- reportOptsNoUpdate :: Lens' c ReportOpts
- accountlistmode :: Lens' c AccountListMode
- average :: Lens' c Bool
- balance_base_url :: Lens' c (Maybe Text)
- balanceaccum :: Lens' c BalanceAccumulation
- balancecalc :: Lens' c BalanceCalculation
- budgetpat :: Lens' c (Maybe Text)
- color__ :: Lens' c Bool
- conversionop :: Lens' c (Maybe ConversionOp)
- date2NoUpdate :: Lens' c Bool
- declared :: Lens' c Bool
- depthNoUpdate :: Lens' c DepthSpec
- drop__ :: Lens' c Int
- empty__ :: Lens' c Bool
- format :: Lens' c StringFormat
- infer_prices :: Lens' c Bool
- interval :: Lens' c Interval
- invert :: Lens' c Bool
- layout :: Lens' c Layout
- no_elide :: Lens' c Bool
- no_total :: Lens' c Bool
- normalbalance :: Lens' c (Maybe NormalSign)
- percent :: Lens' c Bool
- periodNoUpdate :: Lens' c Period
- pretty :: Lens' c Bool
- querystringNoUpdate :: Lens' c [Text]
- realNoUpdate :: Lens' c Bool
- related :: Lens' c Bool
- row_total :: Lens' c Bool
- show_costs :: Lens' c Bool
- sort_amount :: Lens' c Bool
- sortspec :: Lens' c SortSpec
- statusesNoUpdate :: Lens' c [Status]
- summary_only :: Lens' c Bool
- transpose__ :: Lens' c Bool
- txn_dates :: Lens' c Bool
- value :: Lens' c (Maybe ValuationType)
- class HasReportOptsNoUpdate a => HasReportOpts a where
- reportOpts :: ReportableLens' a ReportOpts
- period :: ReportableLens' a Period
- statuses :: ReportableLens' a [Status]
- depth :: ReportableLens' a DepthSpec
- date2 :: ReportableLens' a Bool
- real :: ReportableLens' a Bool
- querystring :: ReportableLens' a [Text]
- data ReportSpec = ReportSpec {
- _rsReportOpts :: ReportOpts
- _rsDay :: Day
- _rsQuery :: Query
- _rsQueryOpts :: [QueryOpt]
- class HasReportSpec c where
- reportSpec :: Lens' c ReportSpec
- rsDay :: Lens' c Day
- rsQuery :: Lens' c Query
- rsQueryOpts :: Lens' c [QueryOpt]
- rsReportOpts :: Lens' c ReportOpts
- data SortField
- type SortSpec = [SortField]
- sortKeysDescription :: [Char]
- overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t
- setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t
- data BalanceCalculation
- data BalanceAccumulation
- data AccountListMode
- data ValuationType
- data Layout
- = LayoutWide (Maybe Int)
- | LayoutTall
- | LayoutBare
- | LayoutTidy
- defreportopts :: ReportOpts
- rawOptsToReportOpts :: Day -> Bool -> RawOpts -> ReportOpts
- defreportspec :: ReportSpec
- defsortspec :: SortSpec
- setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec
- reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
- updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
- updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec
- rawOptsToReportSpec :: Day -> Bool -> RawOpts -> Either String ReportSpec
- balanceAccumulationOverride :: RawOpts -> Maybe BalanceAccumulation
- flat_ :: ReportOpts -> Bool
- tree_ :: ReportOpts -> Bool
- reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts
- simplifyStatuses :: Ord a => [a] -> [a]
- whichDate :: ReportOpts -> WhichDate
- journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal
- journalValueAndFilterPostingsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
- journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
- journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
- mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount
- valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
- intervalFromRawOpts :: RawOpts -> Interval
- queryFromFlags :: ReportOpts -> Query
- transactionDateFn :: ReportOpts -> Transaction -> Day
- postingDateFn :: ReportOpts -> Posting -> Day
- reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
- reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
- reportStartDate :: Journal -> ReportSpec -> Maybe Day
- reportEndDate :: Journal -> ReportSpec -> Maybe Day
- reportPeriodStart :: ReportSpec -> Maybe Day
- reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day
- reportPeriodLastDay :: ReportSpec -> Maybe Day
- reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
- reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text
Documentation
data ReportOpts #
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
class HasReportOptsNoUpdate c where #
Lenses for ReportOpts.
Minimal complete definition
Methods
reportOptsNoUpdate :: Lens' c ReportOpts #
accountlistmode :: Lens' c AccountListMode #
balance_base_url :: Lens' c (Maybe Text) #
balanceaccum :: Lens' c BalanceAccumulation #
balancecalc :: Lens' c BalanceCalculation #
budgetpat :: Lens' c (Maybe Text) #
conversionop :: Lens' c (Maybe ConversionOp) #
date2NoUpdate :: Lens' c Bool #
depthNoUpdate :: Lens' c DepthSpec #
format :: Lens' c StringFormat #
infer_prices :: Lens' c Bool #
interval :: Lens' c Interval #
normalbalance :: Lens' c (Maybe NormalSign) #
periodNoUpdate :: Lens' c Period #
querystringNoUpdate :: Lens' c [Text] #
realNoUpdate :: Lens' c Bool #
show_costs :: Lens' c Bool #
sort_amount :: Lens' c Bool #
sortspec :: Lens' c SortSpec #
statusesNoUpdate :: Lens' c [Status] #
summary_only :: Lens' c Bool #
transpose__ :: Lens' c Bool #
value :: Lens' c (Maybe ValuationType) #
Instances
class HasReportOptsNoUpdate a => HasReportOpts a where #
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 is invalid or unsupported, please correct it:\n(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 #
period :: ReportableLens' a Period #
statuses :: ReportableLens' a [Status] #
depth :: ReportableLens' a DepthSpec #
date2 :: ReportableLens' a Bool #
real :: ReportableLens' a Bool #
querystring :: ReportableLens' a [Text] #
Instances
HasReportOpts ReportOpts # | |
Defined in Hledger.Reports.ReportOptions Methods reportOpts :: ReportableLens' ReportOpts ReportOpts # period :: ReportableLens' ReportOpts Period # statuses :: ReportableLens' ReportOpts [Status] # depth :: ReportableLens' ReportOpts DepthSpec # date2 :: ReportableLens' ReportOpts Bool # real :: ReportableLens' ReportOpts Bool # querystring :: ReportableLens' ReportOpts [Text] # | |
HasReportOpts ReportSpec # | |
Defined in Hledger.Reports.ReportOptions Methods reportOpts :: ReportableLens' ReportSpec ReportOpts # period :: ReportableLens' ReportSpec Period # statuses :: ReportableLens' ReportSpec [Status] # depth :: ReportableLens' ReportSpec DepthSpec # date2 :: ReportableLens' ReportSpec Bool # real :: ReportableLens' ReportSpec Bool # querystring :: ReportableLens' ReportSpec [Text] # |
data ReportSpec #
A fully-determined set of report parameters (report options with all partial values made total, eg the begin and end dates are known, avoiding date/regex errors; plus the reporting date), and the query successfully calculated from them.
If you change the report options or date in one of these, you should
use reportOptsToSpec
to regenerate the whole thing, avoiding inconsistency.
Constructors
ReportSpec | |
Fields
|
Instances
class HasReportSpec c where #
Minimal complete definition
Methods
reportSpec :: Lens' c ReportSpec #
rsQueryOpts :: Lens' c [QueryOpt] #
rsReportOpts :: Lens' c ReportOpts #
Instances
HasReportSpec ReportSpec # | |
Defined in Hledger.Reports.ReportOptions Methods reportSpec :: Lens' ReportSpec ReportSpec # rsDay :: Lens' ReportSpec Day # rsQuery :: Lens' ReportSpec Query # rsQueryOpts :: Lens' ReportSpec [QueryOpt] # |
Constructors
AbsAmount' Bool | |
Account' Bool | |
Amount' Bool | |
Date' Bool | |
Description' Bool |
sortKeysDescription :: [Char] #
overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t #
Apply a function over a lens, but report on failure.
setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t #
Set a field using a lens, but report on failure.
data BalanceCalculation #
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. |
CalcPostingsCount | Number of postings in the period. |
Instances
Default BalanceCalculation # | |
Defined in Hledger.Reports.ReportOptions Methods | |
Show BalanceCalculation # | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> BalanceCalculation -> ShowS # show :: BalanceCalculation -> String # showList :: [BalanceCalculation] -> ShowS # | |
Eq BalanceCalculation # | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: BalanceCalculation -> BalanceCalculation -> Bool # (/=) :: BalanceCalculation -> BalanceCalculation -> Bool # |
data BalanceAccumulation #
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. |
Instances
Default BalanceAccumulation # | |
Defined in Hledger.Reports.ReportOptions Methods | |
Show BalanceAccumulation # | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> BalanceAccumulation -> ShowS # show :: BalanceAccumulation -> String # showList :: [BalanceAccumulation] -> ShowS # | |
Eq BalanceAccumulation # | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: BalanceAccumulation -> BalanceAccumulation -> Bool # (/=) :: BalanceAccumulation -> BalanceAccumulation -> Bool # |
data AccountListMode #
Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
Instances
Default AccountListMode # | |
Defined in Hledger.Reports.ReportOptions Methods def :: AccountListMode # | |
Show AccountListMode # | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> AccountListMode -> ShowS # show :: AccountListMode -> String # showList :: [AccountListMode] -> ShowS # | |
Eq AccountListMode # | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: AccountListMode -> AccountListMode -> Bool # (/=) :: AccountListMode -> AccountListMode -> Bool # |
data ValuationType #
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
Show ValuationType # | |
Defined in Hledger.Data.Valuation Methods showsPrec :: Int -> ValuationType -> ShowS # show :: ValuationType -> String # showList :: [ValuationType] -> ShowS # | |
Eq ValuationType # | |
Defined in Hledger.Data.Valuation Methods (==) :: ValuationType -> ValuationType -> Bool # (/=) :: ValuationType -> ValuationType -> Bool # |
Constructors
LayoutWide (Maybe Int) | |
LayoutTall | |
LayoutBare | |
LayoutTidy |
rawOptsToReportOpts :: Day -> Bool -> RawOpts -> ReportOpts #
Generate a ReportOpts from raw command-line input, given a day and whether to use ANSI colour/styles in standard output. 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,
defsortspec :: SortSpec #
setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec #
Set the default ConversionOp.
reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec #
Generate a ReportSpec from a set of ReportOpts on a given day.
updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec #
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 #
Like updateReportSpec, but takes a ReportOpts-modifying function.
rawOptsToReportSpec :: Day -> Bool -> RawOpts -> Either String ReportSpec #
Generate a ReportSpec from RawOpts and a provided day, or return an error string if there are regular expression errors.
flat_ :: ReportOpts -> Bool #
tree_ :: ReportOpts -> Bool #
Legacy-compatible convenience aliases for accountlistmode_.
reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts #
Add/remove this status from the status list. Used by hledger-ui.
simplifyStatuses :: Ord a => [a] -> [a] #
Reduce a list of statuses to just one of each status, and if all statuses are present return the empty list.
whichDate :: ReportOpts -> WhichDate #
Report which date we will report on based on --date2.
journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal #
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.
journalValueAndFilterPostingsWith :: ReportSpec -> Journal -> PriceOracle -> Journal #
Like journalValueAndFilterPostings
, but takes a PriceOracle
as an argument.
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal #
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 #
Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount #
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) #
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 #
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 #
Convert report options to a query, ignoring any non-flag command line arguments.
transactionDateFn :: ReportOpts -> Transaction -> Day #
Select the Transaction date accessor based on --date2.
postingDateFn :: ReportOpts -> Posting -> Day #
Select the Posting date accessor based on --date2.
reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan]) #
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]) #
Like reportSpan, but uses both primary and secondary dates when calculating the span.
reportStartDate :: Journal -> ReportSpec -> Maybe Day #
reportEndDate :: Journal -> ReportSpec -> Maybe Day #
reportPeriodStart :: ReportSpec -> Maybe Day #
reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day #
reportPeriodLastDay :: ReportSpec -> Maybe Day #
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day #
reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text #
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).