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

47 lines
1.3 KiB
Haskell
Raw Normal View History

2018-09-04 22:23:07 +03:00
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
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
import Data.List
import Data.Ord
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 =
sortBy (comparing date) $ filter (q `matchesTransaction`) ts
where
date = transactionDateFn opts
ts = jtxns $ journalSelectingAmountFromOpts opts j
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