hledger/hledger-lib/Hledger/Reports/EntriesReport.hs

91 lines
3.3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables #-}
2014-03-20 04:11:48 +04:00
{-|
Journal entries report, used by the print command.
-}
module Hledger.Reports.EntriesReport (
EntriesReport,
EntriesReportItem,
entriesReport,
-- * Tests
2018-09-06 23:08:26 +03:00
tests_EntriesReport
2014-03-20 04:11:48 +04:00
)
where
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
import Control.Applicative ((<|>))
2014-03-20 04:11:48 +04:00
import Data.List
import Data.Maybe
2014-03-20 04:11:48 +04:00
import Data.Ord
import Data.Time.Calendar (Day, addDays)
2014-03-20 04:11:48 +04:00
import Hledger.Data
import Hledger.Query
import Hledger.Reports.ReportOptions
import Hledger.Utils
2014-03-20 04:11:48 +04:00
-- | A journal entries report is a list of whole transactions as
-- originally entered in the journal (mostly). This is used by eg
-- hledger's print command and hledger-web's journal entries view.
type EntriesReport = [EntriesReportItem]
type EntriesReportItem = Transaction
-- | Select transactions for an entries report.
entriesReport :: ReportOpts -> Query -> Journal -> EntriesReport
entriesReport opts q j =
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
(if value_ opts then erValue opts j else id) $
2014-03-20 04:11:48 +04:00
sortBy (comparing date) $ filter (q `matchesTransaction`) ts
where
date = transactionDateFn opts
ts = jtxns $ journalSelectingAmountFromOpts opts j
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
-- | Convert all the posting amounts in an EntriesReport to their
-- default valuation commodities. This means using the Journal's most
-- recent applicable market prices before the valuation date.
-- The valuation date is set with --value-date and can be:
-- a custom date;
-- the posting date;
-- the last day in the report period, or in the journal if no period
-- (or the posting date, if journal is empty - shouldn't happen);
-- or today's date (gives an error if today_ is not set in ReportOpts).
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
erValue :: ReportOpts -> Journal -> EntriesReport -> EntriesReport
erValue ropts@ReportOpts{..} j ts =
map txnvalue ts
where
txnvalue t@Transaction{..} = t{tpostings=map postingvalue tpostings}
postingvalue p@Posting{..} = p{pamount=mixedAmountValue prices d pamount}
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
where
-- prices are in parse order - sort into date then parse order,
-- & reversed for quick lookup of the latest price.
prices = reverse $ sortOn mpdate $ jmarketprices j
-- Get the last day of the report period.
-- Will be Nothing if no report period is specified, or also
-- if ReportOpts does not have today_ set, since we need that
-- to get the report period robustly.
mperiodlastday :: Maybe Day = do
t <- today_
let q = queryFromOpts t ropts
qend <- queryEndDate False q
return $ addDays (-1) qend
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
mperiodorjournallastday = mperiodlastday <|> journalEndDate False j
d = case value_at_ of
AtTransaction -> postingDate p
AtPeriod -> fromMaybe (postingDate p) mperiodorjournallastday
AtNow -> case today_ of
Just d -> d
Nothing -> error' "ReportOpts today_ is unset so could not satisfy --value-at=now"
AtDate d -> d
speed up -V/--value by converting reports, not the journal (#999) Instead of converting all journal amounts to value early on, we now convert just the report amounts to value, before rendering. This was basically how it originally worked (for the balance command), but now it's built in to the four basic reports used by print, register, balance and their variants - Entries, Postings, Balance, MultiBalance - each of which now has its own xxValue helper. This should mostly fix -V's performance when there are many transactions and prices (the price lookups could still be optimised), and allow more flexibility for report-specific value calculations. +------------------------------------------++-----------------+-------------------+--------------------------+ | || hledger.999.pre | hledger.999.1sort | hledger.999.after-report | +==========================================++=================+===================+==========================+ | -f examples/1000x1000x10.journal bal -V || 1.08 | 0.96 | 0.76 | | -f examples/2000x1000x10.journal bal -V || 1.65 | 1.05 | 0.73 | | -f examples/3000x1000x10.journal bal -V || 2.43 | 1.58 | 0.84 | | -f examples/4000x1000x10.journal bal -V || 4.39 | 1.96 | 0.93 | | -f examples/5000x1000x10.journal bal -V || 7.75 | 2.99 | 1.07 | | -f examples/6000x1000x10.journal bal -V || 11.21 | 3.72 | 1.16 | | -f examples/7000x1000x10.journal bal -V || 16.91 | 4.72 | 1.19 | | -f examples/8000x1000x10.journal bal -V || 27.10 | 9.83 | 1.40 | | -f examples/9000x1000x10.journal bal -V || 39.73 | 15.00 | 1.51 | | -f examples/10000x1000x10.journal bal -V || 50.72 | 25.61 | 2.15 | +------------------------------------------++-----------------+-------------------+--------------------------+ There's one new limitation, not yet resolved: -V once again can pick a valuation date in the future, if no report end date is specified and the journal has future-dated transactions. We prefer to avoid that, but reports currently are pure and don't have access to today's date.
2019-04-24 03:39:01 +03:00
2018-09-06 23:08:26 +03:00
tests_EntriesReport = tests "EntriesReport" [
2018-09-04 22:23:07 +03:00
tests "entriesReport" [
test "not acct" $ (length $ entriesReport defreportopts (Not $ Acct "bank") samplejournal) `is` 1
,test "date" $ (length $ entriesReport defreportopts (Date $ mkdatespan "2008/06/01" "2008/07/01") samplejournal) `is` 3
]
]
2014-03-20 04:11:48 +04:00