2021-05-13 12:00:43 +03:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE 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
|
|
|
|
|
2020-08-26 11:11:20 +03:00
|
|
|
import Data.List (sortBy)
|
|
|
|
import Data.Ord (comparing)
|
|
|
|
import Data.Time (fromGregorian)
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
import Hledger.Data
|
2021-05-13 12:00:43 +03:00
|
|
|
import Hledger.Query (Query(..))
|
2014-03-20 04:11:48 +04:00
|
|
|
import Hledger.Reports.ReportOptions
|
2019-07-15 13:28:52 +03:00
|
|
|
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.
|
2020-09-16 04:45:52 +03:00
|
|
|
entriesReport :: ReportSpec -> Journal -> EntriesReport
|
2021-05-13 12:00:43 +03:00
|
|
|
entriesReport rspec@ReportSpec{rsOpts=ropts} =
|
|
|
|
sortBy (comparing $ transactionDateFn ropts) . jtxns . filterJournalTransactions (rsQuery rspec)
|
|
|
|
. journalApplyValuationFromOpts rspec{rsOpts=ropts{show_costs_=True}}
|
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" [
|
2020-09-16 04:45:52 +03:00
|
|
|
test "not acct" $ (length $ entriesReport defreportspec{rsQuery=Not . Acct $ toRegex' "bank"} samplejournal) @?= 1
|
|
|
|
,test "date" $ (length $ entriesReport defreportspec{rsQuery=Date $ DateSpan (Just $ fromGregorian 2008 06 01) (Just $ fromGregorian 2008 07 01)} samplejournal) @?= 3
|
2018-09-04 22:23:07 +03:00
|
|
|
]
|
|
|
|
]
|
2014-03-20 04:11:48 +04:00
|
|
|
|