Safe Haskell | None |
---|---|
Language | Haskell2010 |
Options common to most hledger reports.
Synopsis
- data ReportOpts = ReportOpts {
- period_ :: Period
- interval_ :: Interval
- statuses_ :: [Status]
- cost_ :: Costing
- value_ :: Maybe ValuationType
- infer_value_ :: Bool
- depth_ :: Maybe Int
- date2_ :: Bool
- empty_ :: Bool
- no_elide_ :: Bool
- real_ :: Bool
- format_ :: StringFormat
- querystring_ :: [Text]
- average_ :: Bool
- related_ :: Bool
- txn_dates_ :: Bool
- reporttype_ :: ReportType
- balancetype_ :: BalanceType
- accountlistmode_ :: AccountListMode
- drop_ :: Int
- row_total_ :: Bool
- no_total_ :: Bool
- pretty_tables_ :: Bool
- sort_amount_ :: Bool
- percent_ :: Bool
- invert_ :: Bool
- normalbalance_ :: Maybe NormalSign
- color_ :: Bool
- forecast_ :: Maybe DateSpan
- transpose_ :: Bool
- data ReportSpec = ReportSpec {
- rsOpts :: ReportOpts
- rsToday :: Day
- rsQuery :: Query
- rsQueryOpts :: [QueryOpt]
- data ReportType
- data BalanceType
- data AccountListMode
- data ValuationType
- defreportopts :: ReportOpts
- rawOptsToReportOpts :: RawOpts -> IO ReportOpts
- defreportspec :: ReportSpec
- reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
- updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
- updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec
- rawOptsToReportSpec :: RawOpts -> IO ReportSpec
- balanceTypeOverride :: RawOpts -> Maybe BalanceType
- flat_ :: ReportOpts -> Bool
- tree_ :: ReportOpts -> Bool
- reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts
- simplifyStatuses :: Ord a => [a] -> [a]
- whichDateFromOpts :: ReportOpts -> WhichDate
- journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal
- intervalFromRawOpts :: RawOpts -> Interval
- forecastPeriodFromRawOpts :: Day -> RawOpts -> Maybe DateSpan
- queryFromFlags :: ReportOpts -> Query
- transactionDateFn :: ReportOpts -> Transaction -> Day
- postingDateFn :: ReportOpts -> Posting -> Day
- reportSpan :: Journal -> ReportSpec -> DateSpan
- reportSpanBothDates :: Journal -> ReportSpec -> 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
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.
ReportOpts | |
|
Instances
Show ReportOpts Source # | |
Defined in Hledger.Reports.ReportOptions showsPrec :: Int -> ReportOpts -> ShowS # show :: ReportOpts -> String # showList :: [ReportOpts] -> ShowS # | |
Default ReportOpts Source # | |
Defined in Hledger.Reports.ReportOptions def :: ReportOpts # |
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.
ReportSpec | |
|
Instances
Show ReportSpec Source # | |
Defined in Hledger.Reports.ReportOptions showsPrec :: Int -> ReportSpec -> ShowS # show :: ReportSpec -> String # showList :: [ReportSpec] -> ShowS # | |
Default ReportSpec Source # | |
Defined in Hledger.Reports.ReportOptions def :: ReportSpec # |
data ReportType Source #
What is calculated and shown in each cell in a balance report.
ChangeReport | The sum of posting amounts. |
BudgetReport | The sum of posting amounts and the goal. |
ValueChangeReport | The change of value of period-end historical values. |
Instances
Eq ReportType Source # | |
Defined in Hledger.Reports.ReportOptions (==) :: ReportType -> ReportType -> Bool # (/=) :: ReportType -> ReportType -> Bool # | |
Show ReportType Source # | |
Defined in Hledger.Reports.ReportOptions showsPrec :: Int -> ReportType -> ShowS # show :: ReportType -> String # showList :: [ReportType] -> ShowS # | |
Default ReportType Source # | |
Defined in Hledger.Reports.ReportOptions def :: ReportType # |
data BalanceType Source #
Which "accumulation method" is being shown in a balance report.
PeriodChange | The accumulate change over a single period. |
CumulativeChange | The accumulated change across multiple periods. |
HistoricalBalance | The historical ending balance, including the effect of all postings before the report period. Unless altered by, a query, this is what you would see on a bank statement. |
Instances
Eq BalanceType Source # | |
Defined in Hledger.Reports.ReportOptions (==) :: BalanceType -> BalanceType -> Bool # (/=) :: BalanceType -> BalanceType -> Bool # | |
Show BalanceType Source # | |
Defined in Hledger.Reports.ReportOptions showsPrec :: Int -> BalanceType -> ShowS # show :: BalanceType -> String # showList :: [BalanceType] -> ShowS # | |
Default BalanceType Source # | |
Defined in Hledger.Reports.ReportOptions def :: BalanceType # |
data AccountListMode Source #
Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
Instances
Eq AccountListMode Source # | |
Defined in Hledger.Reports.ReportOptions (==) :: AccountListMode -> AccountListMode -> Bool # (/=) :: AccountListMode -> AccountListMode -> Bool # | |
Show AccountListMode Source # | |
Defined in Hledger.Reports.ReportOptions showsPrec :: Int -> AccountListMode -> ShowS # show :: AccountListMode -> String # showList :: [AccountListMode] -> ShowS # | |
Default AccountListMode Source # | |
Defined in Hledger.Reports.ReportOptions def :: AccountListMode # |
data ValuationType Source #
What kind of value conversion should be done on amounts ? CLI: --value=then|end|now|DATE[,COMM]
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
Eq ValuationType Source # | |
Defined in Hledger.Data.Valuation (==) :: ValuationType -> ValuationType -> Bool # (/=) :: ValuationType -> ValuationType -> Bool # | |
Show ValuationType Source # | |
Defined in Hledger.Data.Valuation showsPrec :: Int -> ValuationType -> ShowS # show :: ValuationType -> String # showList :: [ValuationType] -> ShowS # |
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, rsOpts, querystring_, etc.) are in sync.
updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec Source #
Like updateReportSpec, but takes a ReportOpts-modifying function.
rawOptsToReportSpec :: RawOpts -> IO ReportSpec Source #
Generate a ReportSpec from RawOpts and the current date.
flat_ :: ReportOpts -> Bool Source #
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.
whichDateFromOpts :: ReportOpts -> WhichDate Source #
Report which date we will report on based on --date2.
journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal Source #
Convert this journal's postings' amounts to cost using their transaction prices, if specified by options (-B/--cost). Maybe soon superseded by newer valuation code.
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.
forecastPeriodFromRawOpts :: Day -> RawOpts -> Maybe DateSpan Source #
get period expression from --forecast option
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 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. The boolean argument flags whether primary and secondary dates are considered equivalently.
reportSpanBothDates :: Journal -> ReportSpec -> DateSpan Source #
Like reportSpan, but uses both primary and secondary dates when calculating the span.
reportStartDate :: Journal -> ReportSpec -> Maybe Day Source #
reportEndDate :: Journal -> ReportSpec -> Maybe Day Source #
reportPeriodStart :: ReportSpec -> Maybe Day Source #
reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day Source #
reportPeriodLastDay :: ReportSpec -> Maybe Day Source #
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day Source #