Safe Haskell | None |
---|---|
Language | Haskell2010 |
Options common to most hledger reports.
Synopsis
- data ReportOpts = ReportOpts {
- today_ :: Maybe Day
- period_ :: Period
- interval_ :: Interval
- statuses_ :: [Status]
- value_ :: Maybe ValuationType
- depth_ :: Maybe Int
- display_ :: Maybe DisplayExp
- date2_ :: Bool
- empty_ :: Bool
- no_elide_ :: Bool
- real_ :: Bool
- format_ :: Maybe FormatStr
- query_ :: String
- average_ :: Bool
- related_ :: Bool
- 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_ :: Bool
- transpose_ :: Bool
- data BalanceType
- data AccountListMode
- data ValuationType
- type FormatStr = String
- defreportopts :: ReportOpts
- rawOptsToReportOpts :: RawOpts -> IO ReportOpts
- checkReportOpts :: ReportOpts -> ReportOpts
- 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
- queryFromOpts :: Day -> ReportOpts -> Query
- queryFromOptsOnly :: Day -> ReportOpts -> Query
- queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt]
- transactionDateFn :: ReportOpts -> Transaction -> Day
- postingDateFn :: ReportOpts -> Posting -> Day
- reportSpan :: Journal -> ReportOpts -> IO DateSpan
- reportStartDate :: Journal -> ReportOpts -> IO (Maybe Day)
- reportEndDate :: Journal -> ReportOpts -> IO (Maybe Day)
- specifiedStartEndDates :: ReportOpts -> IO (Maybe Day, Maybe Day)
- specifiedStartDate :: ReportOpts -> IO (Maybe Day)
- specifiedEndDate :: ReportOpts -> IO (Maybe Day)
- reportPeriodStart :: ReportOpts -> Maybe Day
- reportPeriodOrJournalStart :: ReportOpts -> Journal -> Maybe Day
- reportPeriodLastDay :: ReportOpts -> Maybe Day
- reportPeriodOrJournalLastDay :: ReportOpts -> Journal -> Maybe Day
- valuationTypeIsCost :: ReportOpts -> Bool
- valuationTypeIsDefaultValue :: ReportOpts -> Bool
- tests_ReportOptions :: TestTree
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
Data ReportOpts Source # | |
Defined in Hledger.Reports.ReportOptions gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportOpts -> c ReportOpts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportOpts # toConstr :: ReportOpts -> Constr # dataTypeOf :: ReportOpts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReportOpts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportOpts) # gmapT :: (forall b. Data b => b -> b) -> ReportOpts -> ReportOpts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportOpts -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportOpts -> r # gmapQ :: (forall d. Data d => d -> u) -> ReportOpts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportOpts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts # | |
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 BalanceType Source #
Which "balance" is being shown in a balance report.
PeriodChange | The change of balance in each 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
data AccountListMode Source #
Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
Instances
data ValuationType Source #
What kind of value conversion should be done on amounts ? UI: --value=cost|end|now|DATE[,COMM]
AtCost (Maybe CommoditySymbol) | convert to cost commodity using transaction prices, then optionally to given commodity using market prices at posting date |
AtEnd (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using market prices at period end(s) |
AtNow (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using current market prices |
AtDate Day (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using market prices on some date |
AtDefault (Maybe CommoditySymbol) | works like AtNow in single period reports, like AtEnd in multiperiod reports |
Instances
Eq ValuationType Source # | |
Defined in Hledger.Data.Valuation (==) :: ValuationType -> ValuationType -> Bool # (/=) :: ValuationType -> ValuationType -> Bool # | |
Data ValuationType Source # | |
Defined in Hledger.Data.Valuation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValuationType -> c ValuationType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ValuationType # toConstr :: ValuationType -> Constr # dataTypeOf :: ValuationType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ValuationType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ValuationType) # gmapT :: (forall b. Data b => b -> b) -> ValuationType -> ValuationType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValuationType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValuationType -> r # gmapQ :: (forall d. Data d => d -> u) -> ValuationType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ValuationType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # | |
Show ValuationType Source # | |
Defined in Hledger.Data.Valuation showsPrec :: Int -> ValuationType -> ShowS # show :: ValuationType -> String # showList :: [ValuationType] -> ShowS # |
checkReportOpts :: ReportOpts -> ReportOpts Source #
Do extra validation of report options, raising an error if there's a problem.
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/--value=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.
queryFromOpts :: Day -> ReportOpts -> Query Source #
Convert report options and arguments to a query.
queryFromOptsOnly :: Day -> ReportOpts -> Query Source #
Convert report options to a query, ignoring any non-flag command line arguments.
queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt] Source #
Convert report options and arguments to query options.
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 -> ReportOpts -> IO 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. Needs IO to parse smart dates in options/queries.
reportStartDate :: Journal -> ReportOpts -> IO (Maybe Day) Source #
reportEndDate :: Journal -> ReportOpts -> IO (Maybe Day) Source #
specifiedStartEndDates :: ReportOpts -> IO (Maybe Day, Maybe Day) Source #
The specified report start/end dates are the dates specified by options or queries, if any. Needs IO to parse smart dates in options/queries.
specifiedStartDate :: ReportOpts -> IO (Maybe Day) Source #
specifiedEndDate :: ReportOpts -> IO (Maybe Day) Source #
reportPeriodStart :: ReportOpts -> Maybe Day Source #
reportPeriodOrJournalStart :: ReportOpts -> Journal -> Maybe Day Source #
reportPeriodLastDay :: ReportOpts -> Maybe Day Source #
reportPeriodOrJournalLastDay :: ReportOpts -> Journal -> Maybe Day Source #
valuationTypeIsCost :: ReportOpts -> Bool Source #