tests: ReportOptions -> easytest
This commit is contained in:
parent
3b63c2ff2f
commit
241d0dbebd
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
||||||
{-|
|
{-|
|
||||||
|
|
||||||
Generate several common kinds of report from a journal, as \"*Report\" -
|
Generate several common kinds of report from a journal, as \"*Report\" -
|
||||||
@ -18,9 +18,9 @@ module Hledger.Reports (
|
|||||||
module Hledger.Reports.MultiBalanceReports,
|
module Hledger.Reports.MultiBalanceReports,
|
||||||
module Hledger.Reports.BudgetReport,
|
module Hledger.Reports.BudgetReport,
|
||||||
-- module Hledger.Reports.BalanceHistoryReport,
|
-- module Hledger.Reports.BalanceHistoryReport,
|
||||||
|
|
||||||
-- * Tests
|
-- * Tests
|
||||||
tests_Hledger_Reports
|
tests_Hledger_Reports,
|
||||||
|
easytests_Reports
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -36,11 +36,13 @@ import Hledger.Reports.BudgetReport
|
|||||||
import Hledger.Utils.Test
|
import Hledger.Utils.Test
|
||||||
|
|
||||||
tests_Hledger_Reports = TestList $
|
tests_Hledger_Reports = TestList $
|
||||||
-- ++ tests_isInterestingIndented
|
|
||||||
[
|
[
|
||||||
tests_Hledger_Reports_ReportOptions,
|
|
||||||
tests_Hledger_Reports_EntriesReport,
|
tests_Hledger_Reports_EntriesReport,
|
||||||
tests_Hledger_Reports_PostingsReport,
|
tests_Hledger_Reports_PostingsReport,
|
||||||
tests_Hledger_Reports_BalanceReport,
|
tests_Hledger_Reports_BalanceReport,
|
||||||
tests_Hledger_Reports_MultiBalanceReport
|
tests_Hledger_Reports_MultiBalanceReport
|
||||||
]
|
]
|
||||||
|
|
||||||
|
easytests_Reports = tests "Reports" [
|
||||||
|
easytests_ReportOptions
|
||||||
|
]
|
||||||
|
|||||||
@ -1,10 +1,11 @@
|
|||||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable #-}
|
|
||||||
{-|
|
{-|
|
||||||
|
|
||||||
Options common to most hledger reports.
|
Options common to most hledger reports.
|
||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable #-}
|
||||||
|
|
||||||
module Hledger.Reports.ReportOptions (
|
module Hledger.Reports.ReportOptions (
|
||||||
ReportOpts(..),
|
ReportOpts(..),
|
||||||
BalanceType(..),
|
BalanceType(..),
|
||||||
@ -32,7 +33,7 @@ module Hledger.Reports.ReportOptions (
|
|||||||
specifiedStartDate,
|
specifiedStartDate,
|
||||||
specifiedEndDate,
|
specifiedEndDate,
|
||||||
|
|
||||||
tests_Hledger_Reports_ReportOptions
|
easytests_ReportOptions
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -51,7 +52,7 @@ import Text.Megaparsec.Error
|
|||||||
|
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Query
|
import Hledger.Query
|
||||||
import Hledger.Utils
|
import Hledger.Utils hiding (is)
|
||||||
|
|
||||||
|
|
||||||
type FormatStr = String
|
type FormatStr = String
|
||||||
@ -371,21 +372,6 @@ queryFromOptsOnly _d ReportOpts{..} = simplifyQuery flagsq
|
|||||||
++ [Or $ map StatusQ statuses_]
|
++ [Or $ map StatusQ statuses_]
|
||||||
++ (maybe [] ((:[]) . Depth) depth_)
|
++ (maybe [] ((:[]) . Depth) depth_)
|
||||||
|
|
||||||
tests_queryFromOpts = [
|
|
||||||
"queryFromOpts" ~: do
|
|
||||||
assertEqual "" Any (queryFromOpts nulldate defreportopts)
|
|
||||||
assertEqual "" (Acct "a") (queryFromOpts nulldate defreportopts{query_="a"})
|
|
||||||
assertEqual "" (Desc "a a") (queryFromOpts nulldate defreportopts{query_="desc:'a a'"})
|
|
||||||
assertEqual "" (Date $ mkdatespan "2012/01/01" "2013/01/01")
|
|
||||||
(queryFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01")
|
|
||||||
,query_="date:'to 2013'"
|
|
||||||
})
|
|
||||||
assertEqual "" (Date2 $ mkdatespan "2012/01/01" "2013/01/01")
|
|
||||||
(queryFromOpts nulldate defreportopts{query_="date2:'in 2012'"})
|
|
||||||
assertEqual "" (Or [Acct "a a", Acct "'b"])
|
|
||||||
(queryFromOpts nulldate defreportopts{query_="'a a' 'b"})
|
|
||||||
]
|
|
||||||
|
|
||||||
-- | Convert report options and arguments to query options.
|
-- | Convert report options and arguments to query options.
|
||||||
queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt]
|
queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt]
|
||||||
queryOptsFromOpts d ReportOpts{..} = flagsqopts ++ argsqopts
|
queryOptsFromOpts d ReportOpts{..} = flagsqopts ++ argsqopts
|
||||||
@ -393,15 +379,6 @@ queryOptsFromOpts d ReportOpts{..} = flagsqopts ++ argsqopts
|
|||||||
flagsqopts = []
|
flagsqopts = []
|
||||||
argsqopts = snd $ parseQuery d (T.pack query_)
|
argsqopts = snd $ parseQuery d (T.pack query_)
|
||||||
|
|
||||||
tests_queryOptsFromOpts = [
|
|
||||||
"queryOptsFromOpts" ~: do
|
|
||||||
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts)
|
|
||||||
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts{query_="a"})
|
|
||||||
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01")
|
|
||||||
,query_="date:'to 2013'"
|
|
||||||
})
|
|
||||||
]
|
|
||||||
|
|
||||||
-- | The effective report span is the start and end dates specified by
|
-- | The effective report span is the start and end dates specified by
|
||||||
-- options or queries, or otherwise the earliest and latest transaction or
|
-- options or queries, or otherwise the earliest and latest transaction or
|
||||||
-- posting dates in the journal. If no dates are specified by options/queries
|
-- posting dates in the journal. If no dates are specified by options/queries
|
||||||
@ -441,7 +418,29 @@ specifiedStartDate ropts = fst <$> specifiedStartEndDates ropts
|
|||||||
specifiedEndDate :: ReportOpts -> IO (Maybe Day)
|
specifiedEndDate :: ReportOpts -> IO (Maybe Day)
|
||||||
specifiedEndDate ropts = snd <$> specifiedStartEndDates ropts
|
specifiedEndDate ropts = snd <$> specifiedStartEndDates ropts
|
||||||
|
|
||||||
|
-- tests
|
||||||
|
|
||||||
|
is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
|
||||||
|
is = flip expectEq'
|
||||||
|
|
||||||
|
easytests_ReportOptions = tests "ReportOptions" [
|
||||||
|
tests "queryFromOpts" [
|
||||||
|
(queryFromOpts nulldate defreportopts) `is` Any
|
||||||
|
,(queryFromOpts nulldate defreportopts{query_="a"}) `is` (Acct "a")
|
||||||
|
,(queryFromOpts nulldate defreportopts{query_="desc:'a a'"}) `is` (Desc "a a")
|
||||||
|
,(queryFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01"),query_="date:'to 2013'" })
|
||||||
|
`is` (Date $ mkdatespan "2012/01/01" "2013/01/01")
|
||||||
|
,(queryFromOpts nulldate defreportopts{query_="date2:'in 2012'"}) `is` (Date2 $ mkdatespan "2012/01/01" "2013/01/01")
|
||||||
|
,(queryFromOpts nulldate defreportopts{query_="'a a' 'b"}) `is` (Or [Acct "a a", Acct "'b"])
|
||||||
|
]
|
||||||
|
|
||||||
|
,tests "queryOptsFromOpts" [
|
||||||
|
(queryOptsFromOpts nulldate defreportopts) `is` []
|
||||||
|
,(queryOptsFromOpts nulldate defreportopts{query_="a"}) `is` []
|
||||||
|
,(queryOptsFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01")
|
||||||
|
,query_="date:'to 2013'"
|
||||||
|
})
|
||||||
|
`is` []
|
||||||
|
]
|
||||||
|
]
|
||||||
|
|
||||||
tests_Hledger_Reports_ReportOptions = TestList $
|
|
||||||
tests_queryFromOpts
|
|
||||||
++ tests_queryOptsFromOpts
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user