mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-07 21:15:19 +03:00
tests: Reports -> easytest
This commit is contained in:
parent
241d0dbebd
commit
09d9fbf487
@ -15,12 +15,12 @@ import Hledger.Utils as X
|
||||
|
||||
tests_Hledger = TestList
|
||||
[
|
||||
tests_Hledger_Reports
|
||||
]
|
||||
|
||||
easytests_Hledger = tests "Hledger" [
|
||||
easytests_Data
|
||||
,easytests_Read
|
||||
,easytests_Query
|
||||
,easytests_Read
|
||||
,easytests_Reports
|
||||
,easytests_Utils
|
||||
]
|
||||
|
@ -19,7 +19,6 @@ module Hledger.Reports (
|
||||
module Hledger.Reports.BudgetReport,
|
||||
-- module Hledger.Reports.BalanceHistoryReport,
|
||||
-- * Tests
|
||||
tests_Hledger_Reports,
|
||||
easytests_Reports
|
||||
)
|
||||
where
|
||||
@ -35,14 +34,12 @@ import Hledger.Reports.BudgetReport
|
||||
-- import Hledger.Reports.BalanceHistoryReport
|
||||
import Hledger.Utils.Test
|
||||
|
||||
tests_Hledger_Reports = TestList $
|
||||
[
|
||||
tests_Hledger_Reports_EntriesReport,
|
||||
tests_Hledger_Reports_PostingsReport,
|
||||
tests_Hledger_Reports_BalanceReport,
|
||||
tests_Hledger_Reports_MultiBalanceReport
|
||||
]
|
||||
|
||||
easytests_Reports = tests "Reports" [
|
||||
easytests_ReportOptions
|
||||
]
|
||||
easytests_BalanceReport
|
||||
,easytests_BudgetReport
|
||||
,easytests_EntriesReport
|
||||
,easytests_MultiBalanceReports
|
||||
,easytests_PostingsReport
|
||||
,easytests_ReportOptions
|
||||
,easytests_TransactionsReports
|
||||
]
|
||||
|
@ -20,7 +20,7 @@ module Hledger.Reports.BalanceReport (
|
||||
flatShowsExclusiveBalance,
|
||||
|
||||
-- * Tests
|
||||
tests_Hledger_Reports_BalanceReport
|
||||
easytests_BalanceReport
|
||||
)
|
||||
where
|
||||
|
||||
@ -32,7 +32,7 @@ import Data.Time.Calendar
|
||||
import Hledger.Data
|
||||
import Hledger.Read (mamountp')
|
||||
import Hledger.Query
|
||||
import Hledger.Utils
|
||||
import Hledger.Utils hiding (is)
|
||||
import Hledger.Reports.ReportOptions
|
||||
|
||||
|
||||
@ -155,216 +155,6 @@ brNegate (is, tot) = (map brItemNegate is, -tot)
|
||||
where
|
||||
brItemNegate (a, a', d, amt) = (a, a', d, -amt)
|
||||
|
||||
tests_balanceReport =
|
||||
let
|
||||
(opts,journal) `gives` r = do
|
||||
let (eitems, etotal) = r
|
||||
(aitems, atotal) = balanceReport opts (queryFromOpts nulldate opts) journal
|
||||
showw (acct,acct',indent,amt) = (acct, acct', indent, showMixedAmountDebug amt)
|
||||
assertEqual "items" (map showw eitems) (map showw aitems)
|
||||
assertEqual "total" (showMixedAmountDebug etotal) (showMixedAmountDebug atotal)
|
||||
usd0 = usd 0
|
||||
in [
|
||||
|
||||
"balanceReport with no args on null journal" ~: do
|
||||
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
|
||||
|
||||
,"balanceReport with no args on sample journal" ~: do
|
||||
(defreportopts, samplejournal) `gives`
|
||||
([
|
||||
("assets","assets",0, mamountp' "$0.00")
|
||||
,("assets:bank","bank",1, mamountp' "$2.00")
|
||||
,("assets:bank:checking","checking",2, mamountp' "$1.00")
|
||||
,("assets:bank:saving","saving",2, mamountp' "$1.00")
|
||||
,("assets:cash","cash",1, mamountp' "$-2.00")
|
||||
,("expenses","expenses",0, mamountp' "$2.00")
|
||||
,("expenses:food","food",1, mamountp' "$1.00")
|
||||
,("expenses:supplies","supplies",1, mamountp' "$1.00")
|
||||
,("income","income",0, mamountp' "$-2.00")
|
||||
,("income:gifts","gifts",1, mamountp' "$-1.00")
|
||||
,("income:salary","salary",1, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with --depth=N" ~: do
|
||||
(defreportopts{depth_=Just 1}, samplejournal) `gives`
|
||||
([
|
||||
("expenses", "expenses", 0, mamountp' "$2.00")
|
||||
,("income", "income", 0, mamountp' "$-2.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with depth:N" ~: do
|
||||
(defreportopts{query_="depth:1"}, samplejournal) `gives`
|
||||
([
|
||||
("expenses", "expenses", 0, mamountp' "$2.00")
|
||||
,("income", "income", 0, mamountp' "$-2.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with a date or secondary date span" ~: do
|
||||
(defreportopts{query_="date:'in 2009'"}, samplejournal2) `gives`
|
||||
([],
|
||||
Mixed [nullamt])
|
||||
(defreportopts{query_="date2:'in 2009'"}, samplejournal2) `gives`
|
||||
([
|
||||
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0,mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with desc:" ~: do
|
||||
(defreportopts{query_="desc:income"}, samplejournal) `gives`
|
||||
([
|
||||
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with not:desc:" ~: do
|
||||
(defreportopts{query_="not:desc:income"}, samplejournal) `gives`
|
||||
([
|
||||
("assets","assets",0, mamountp' "$-1.00")
|
||||
,("assets:bank:saving","bank:saving",1, mamountp' "$1.00")
|
||||
,("assets:cash","cash",1, mamountp' "$-2.00")
|
||||
,("expenses","expenses",0, mamountp' "$2.00")
|
||||
,("expenses:food","food",1, mamountp' "$1.00")
|
||||
,("expenses:supplies","supplies",1, mamountp' "$1.00")
|
||||
,("income:gifts","income:gifts",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with period on a populated period" ~: do
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","assets:bank:checking",0, mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"balanceReport with period on an unpopulated period" ~: do
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}, samplejournal) `gives`
|
||||
([],Mixed [nullamt])
|
||||
|
||||
|
||||
|
||||
{-
|
||||
,"accounts report with account pattern o" ~:
|
||||
defreportopts{patterns_=["o"]} `gives`
|
||||
[" $1 expenses:food"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,"accounts report with account pattern o and --depth 1" ~:
|
||||
defreportopts{patterns_=["o"],depth_=Just 1} `gives`
|
||||
[" $1 expenses"
|
||||
," $-2 income"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,"accounts report with account pattern a" ~:
|
||||
defreportopts{patterns_=["a"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
," $-1 income:salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,"accounts report with account pattern e" ~:
|
||||
defreportopts{patterns_=["e"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
," $2 expenses"
|
||||
," $1 food"
|
||||
," $1 supplies"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," 0"
|
||||
]
|
||||
|
||||
,"accounts report with unmatched parent of two matched subaccounts" ~:
|
||||
defreportopts{patterns_=["cash","saving"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,"accounts report with multi-part account name" ~:
|
||||
defreportopts{patterns_=["expenses:food"]} `gives`
|
||||
[" $1 expenses:food"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,"accounts report with negative account pattern" ~:
|
||||
defreportopts{patterns_=["not:assets"]} `gives`
|
||||
[" $2 expenses"
|
||||
," $1 food"
|
||||
," $1 supplies"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,"accounts report negative account pattern always matches full name" ~:
|
||||
defreportopts{patterns_=["not:e"]} `gives`
|
||||
["--------------------"
|
||||
," 0"
|
||||
]
|
||||
|
||||
,"accounts report negative patterns affect totals" ~:
|
||||
defreportopts{patterns_=["expenses","not:food"]} `gives`
|
||||
[" $1 expenses:supplies"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,"accounts report with -E shows zero-balance accounts" ~:
|
||||
defreportopts{patterns_=["assets"],empty_=True} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank"
|
||||
," 0 checking"
|
||||
," $1 saving"
|
||||
," $-2 cash"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,"accounts report with cost basis" ~: do
|
||||
j <- (readJournal def Nothing $ unlines
|
||||
[""
|
||||
,"2008/1/1 test "
|
||||
," a:b 10h @ $50"
|
||||
," c:d "
|
||||
]) >>= either error' return
|
||||
let j' = journalCanonicaliseAmounts $ journalConvertAmountsToCost j -- enable cost basis adjustment
|
||||
balanceReportAsText defreportopts (balanceReport defreportopts Any j') `is`
|
||||
[" $500 a:b"
|
||||
," $-500 c:d"
|
||||
,"--------------------"
|
||||
," 0"
|
||||
]
|
||||
-}
|
||||
]
|
||||
|
||||
Right samplejournal2 =
|
||||
journalBalanceTransactions False
|
||||
nulljournal{
|
||||
@ -388,13 +178,222 @@ Right samplejournal2 =
|
||||
]
|
||||
}
|
||||
|
||||
-- tests_isInterestingIndented = [
|
||||
-- "isInterestingIndented" ~: do
|
||||
-- let (opts, journal, acctname) `gives` r = isInterestingIndented opts l acctname `is` r
|
||||
-- where l = ledgerFromJournal (queryFromOpts nulldate opts) journal
|
||||
-- tests
|
||||
|
||||
-- (defreportopts, samplejournal, "expenses") `gives` True
|
||||
-- ]
|
||||
is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
|
||||
is = flip expectEq'
|
||||
|
||||
easytests_BalanceReport = tests "BalanceReport" [
|
||||
tests "balanceReport" $
|
||||
let
|
||||
(opts,journal) `gives` r = do
|
||||
let (eitems, etotal) = r
|
||||
(aitems, atotal) = balanceReport opts (queryFromOpts nulldate opts) journal
|
||||
showw (acct,acct',indent,amt) = (acct, acct', indent, showMixedAmountDebug amt)
|
||||
(map showw eitems) `is` (map showw aitems)
|
||||
(showMixedAmountDebug etotal) `is` (showMixedAmountDebug atotal)
|
||||
usd0 = usd 0
|
||||
in [
|
||||
|
||||
test "balanceReport with no args on null journal" $
|
||||
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
|
||||
|
||||
,test "balanceReport with no args on sample journal" $
|
||||
(defreportopts, samplejournal) `gives`
|
||||
([
|
||||
("assets","assets",0, mamountp' "$0.00")
|
||||
,("assets:bank","bank",1, mamountp' "$2.00")
|
||||
,("assets:bank:checking","checking",2, mamountp' "$1.00")
|
||||
,("assets:bank:saving","saving",2, mamountp' "$1.00")
|
||||
,("assets:cash","cash",1, mamountp' "$-2.00")
|
||||
,("expenses","expenses",0, mamountp' "$2.00")
|
||||
,("expenses:food","food",1, mamountp' "$1.00")
|
||||
,("expenses:supplies","supplies",1, mamountp' "$1.00")
|
||||
,("income","income",0, mamountp' "$-2.00")
|
||||
,("income:gifts","gifts",1, mamountp' "$-1.00")
|
||||
,("income:salary","salary",1, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "balanceReport with --depth=N" $
|
||||
(defreportopts{depth_=Just 1}, samplejournal) `gives`
|
||||
([
|
||||
("expenses", "expenses", 0, mamountp' "$2.00")
|
||||
,("income", "income", 0, mamountp' "$-2.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "balanceReport with depth:N" $
|
||||
(defreportopts{query_="depth:1"}, samplejournal) `gives`
|
||||
([
|
||||
("expenses", "expenses", 0, mamountp' "$2.00")
|
||||
,("income", "income", 0, mamountp' "$-2.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,tests "balanceReport with a date or secondary date span" [
|
||||
(defreportopts{query_="date:'in 2009'"}, samplejournal2) `gives`
|
||||
([],
|
||||
Mixed [nullamt])
|
||||
,(defreportopts{query_="date2:'in 2009'"}, samplejournal2) `gives`
|
||||
([
|
||||
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0,mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
]
|
||||
|
||||
,test "balanceReport with desc:" $
|
||||
(defreportopts{query_="desc:income"}, samplejournal) `gives`
|
||||
([
|
||||
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "balanceReport with not:desc:" $
|
||||
(defreportopts{query_="not:desc:income"}, samplejournal) `gives`
|
||||
([
|
||||
("assets","assets",0, mamountp' "$-1.00")
|
||||
,("assets:bank:saving","bank:saving",1, mamountp' "$1.00")
|
||||
,("assets:cash","cash",1, mamountp' "$-2.00")
|
||||
,("expenses","expenses",0, mamountp' "$2.00")
|
||||
,("expenses:food","food",1, mamountp' "$1.00")
|
||||
,("expenses:supplies","supplies",1, mamountp' "$1.00")
|
||||
,("income:gifts","income:gifts",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "balanceReport with period on a populated period" $
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","assets:bank:checking",0, mamountp' "$1.00")
|
||||
,("income:salary","income:salary",0, mamountp' "$-1.00")
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "balanceReport with period on an unpopulated period" $
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}, samplejournal) `gives`
|
||||
([],Mixed [nullamt])
|
||||
|
||||
|
||||
|
||||
{-
|
||||
,test "accounts report with account pattern o" ~:
|
||||
defreportopts{patterns_=["o"]} `gives`
|
||||
[" $1 expenses:food"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,test "accounts report with account pattern o and --depth 1" ~:
|
||||
defreportopts{patterns_=["o"],depth_=Just 1} `gives`
|
||||
[" $1 expenses"
|
||||
," $-2 income"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,test "accounts report with account pattern a" ~:
|
||||
defreportopts{patterns_=["a"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
," $-1 income:salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,test "accounts report with account pattern e" ~:
|
||||
defreportopts{patterns_=["e"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
," $2 expenses"
|
||||
," $1 food"
|
||||
," $1 supplies"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," 0"
|
||||
]
|
||||
|
||||
,test "accounts report with unmatched parent of two matched subaccounts" ~:
|
||||
defreportopts{patterns_=["cash","saving"]} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank:saving"
|
||||
," $-2 cash"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,test "accounts report with multi-part account name" ~:
|
||||
defreportopts{patterns_=["expenses:food"]} `gives`
|
||||
[" $1 expenses:food"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,test "accounts report with negative account pattern" ~:
|
||||
defreportopts{patterns_=["not:assets"]} `gives`
|
||||
[" $2 expenses"
|
||||
," $1 food"
|
||||
," $1 supplies"
|
||||
," $-2 income"
|
||||
," $-1 gifts"
|
||||
," $-1 salary"
|
||||
," $1 liabilities:debts"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,test "accounts report negative account pattern always matches full name" ~:
|
||||
defreportopts{patterns_=["not:e"]} `gives`
|
||||
["--------------------"
|
||||
," 0"
|
||||
]
|
||||
|
||||
,test "accounts report negative patterns affect totals" ~:
|
||||
defreportopts{patterns_=["expenses","not:food"]} `gives`
|
||||
[" $1 expenses:supplies"
|
||||
,"--------------------"
|
||||
," $1"
|
||||
]
|
||||
|
||||
,test "accounts report with -E shows zero-balance accounts" ~:
|
||||
defreportopts{patterns_=["assets"],empty_=True} `gives`
|
||||
[" $-1 assets"
|
||||
," $1 bank"
|
||||
," 0 checking"
|
||||
," $1 saving"
|
||||
," $-2 cash"
|
||||
,"--------------------"
|
||||
," $-1"
|
||||
]
|
||||
|
||||
,test "accounts report with cost basis" $
|
||||
j <- (readJournal def Nothing $ unlines
|
||||
[""
|
||||
,"2008/1/1 test "
|
||||
," a:b 10h @ $50"
|
||||
," c:d "
|
||||
]) >>= either error' return
|
||||
let j' = journalCanonicaliseAmounts $ journalConvertAmountsToCost j -- enable cost basis adjustment
|
||||
balanceReportAsText defreportopts (balanceReport defreportopts Any j') `is`
|
||||
[" $500 a:b"
|
||||
," $-500 c:d"
|
||||
,"--------------------"
|
||||
," 0"
|
||||
]
|
||||
-}
|
||||
]
|
||||
|
||||
]
|
||||
|
||||
tests_Hledger_Reports_BalanceReport = TestList
|
||||
tests_balanceReport
|
||||
|
@ -353,3 +353,8 @@ budgetReportAsTable
|
||||
maybeAccountNameDrop :: ReportOpts -> AccountName -> AccountName
|
||||
maybeAccountNameDrop opts a | flat_ opts = accountNameDrop (drop_ opts) a
|
||||
| otherwise = a
|
||||
|
||||
-- tests
|
||||
|
||||
easytests_BudgetReport = tests "BudgetReport" [
|
||||
]
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
||||
{-|
|
||||
|
||||
Journal entries report, used by the print command.
|
||||
@ -10,7 +10,7 @@ module Hledger.Reports.EntriesReport (
|
||||
EntriesReportItem,
|
||||
entriesReport,
|
||||
-- * Tests
|
||||
tests_Hledger_Reports_EntriesReport
|
||||
easytests_EntriesReport
|
||||
)
|
||||
where
|
||||
|
||||
@ -20,7 +20,7 @@ import Data.Ord
|
||||
import Hledger.Data
|
||||
import Hledger.Query
|
||||
import Hledger.Reports.ReportOptions
|
||||
import Hledger.Utils
|
||||
import Hledger.Utils hiding (is)
|
||||
|
||||
|
||||
-- | A journal entries report is a list of whole transactions as
|
||||
@ -37,13 +37,13 @@ entriesReport opts q j =
|
||||
date = transactionDateFn opts
|
||||
ts = jtxns $ journalSelectingAmountFromOpts opts j
|
||||
|
||||
tests_entriesReport = [
|
||||
"entriesReport" ~: do
|
||||
assertEqual "not acct" 1 (length $ entriesReport defreportopts (Not $ Acct "bank") samplejournal)
|
||||
let sp = mkdatespan "2008/06/01" "2008/07/01"
|
||||
assertEqual "date" 3 (length $ entriesReport defreportopts (Date sp) samplejournal)
|
||||
is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
|
||||
is = flip expectEq'
|
||||
|
||||
easytests_EntriesReport = tests "EntriesReport" [
|
||||
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
|
||||
]
|
||||
]
|
||||
|
||||
tests_Hledger_Reports_EntriesReport = TestList $
|
||||
tests_entriesReport
|
||||
|
||||
|
@ -16,7 +16,7 @@ module Hledger.Reports.MultiBalanceReports (
|
||||
tableAsText,
|
||||
|
||||
-- -- * Tests
|
||||
tests_Hledger_Reports_MultiBalanceReport
|
||||
easytests_MultiBalanceReports
|
||||
)
|
||||
where
|
||||
|
||||
@ -30,7 +30,7 @@ import Text.Tabular.AsciiWide
|
||||
|
||||
import Hledger.Data
|
||||
import Hledger.Query
|
||||
import Hledger.Utils
|
||||
import Hledger.Utils hiding (is)
|
||||
import Hledger.Read (mamountp')
|
||||
import Hledger.Reports.ReportOptions
|
||||
import Hledger.Reports.BalanceReport
|
||||
@ -284,53 +284,6 @@ balanceReportFromMultiBalanceReport opts q j = (rows', total)
|
||||
total = headDef nullmixedamt totals
|
||||
|
||||
|
||||
tests_multiBalanceReport =
|
||||
let
|
||||
(opts,journal) `gives` r = do
|
||||
let (eitems, etotal) = r
|
||||
(MultiBalanceReport (_, aitems, atotal)) = multiBalanceReport opts (queryFromOpts nulldate opts) journal
|
||||
showw (acct,acct',indent,lAmt,amt,amt') = (acct, acct', indent, map showMixedAmountDebug lAmt, showMixedAmountDebug amt, showMixedAmountDebug amt')
|
||||
assertEqual "items" (map showw eitems) (map showw aitems)
|
||||
assertEqual "total" (showMixedAmountDebug etotal) ((\(_, b, _) -> showMixedAmountDebug b) atotal) -- we only check the sum of the totals
|
||||
usd0 = usd 0
|
||||
amount0 = Amount {acommodity="$", aquantity=0, aprice=NoPrice, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asprecision = 2, asdecimalpoint = Just '.', asdigitgroups = Nothing}, amultiplier=False}
|
||||
in [
|
||||
"multiBalanceReport with no args on null journal" ~: do
|
||||
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
|
||||
|
||||
,"multiBalanceReport with -H on a populated period" ~: do
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"multiBalanceReport tests the ability to have a valid history on an empty period" ~: do
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,"multiBalanceReport tests the ability to have a valid history on an empty period (More complex)" ~: do
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("assets:bank:saving","saving",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("assets:cash","cash",2, [mamountp' "$-2.00"], mamountp' "$-2.00",Mixed [amount0 {aquantity=(-2)}])
|
||||
,("expenses:food","food",2, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=(1)}])
|
||||
,("expenses:supplies","supplies",2, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=(1)}])
|
||||
,("income:gifts","gifts",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
]
|
||||
|
||||
-- common rendering helper, XXX here for now
|
||||
|
||||
tableAsText :: ReportOpts -> (a -> String) -> Table String String a -> String
|
||||
@ -347,5 +300,56 @@ tableAsText (ReportOpts{pretty_tables_ = pretty}) showcell =
|
||||
acctswidth = maximum' $ map strWidth (headerContents l)
|
||||
l' = padRightWide acctswidth <$> l
|
||||
|
||||
tests_Hledger_Reports_MultiBalanceReport = TestList
|
||||
tests_multiBalanceReport
|
||||
-- tests
|
||||
|
||||
is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
|
||||
is = flip expectEq'
|
||||
|
||||
easytests_MultiBalanceReports = tests "MultiBalanceReports" [
|
||||
let
|
||||
(opts,journal) `gives` r = do
|
||||
let (eitems, etotal) = r
|
||||
(MultiBalanceReport (_, aitems, atotal)) = multiBalanceReport opts (queryFromOpts nulldate opts) journal
|
||||
showw (acct,acct',indent,lAmt,amt,amt') = (acct, acct', indent, map showMixedAmountDebug lAmt, showMixedAmountDebug amt, showMixedAmountDebug amt')
|
||||
(map showw aitems) `is` (map showw eitems)
|
||||
((\(_, b, _) -> showMixedAmountDebug b) atotal) `is` (showMixedAmountDebug etotal) -- we only check the sum of the totals
|
||||
usd0 = usd 0
|
||||
amount0 = Amount {acommodity="$", aquantity=0, aprice=NoPrice, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asprecision = 2, asdecimalpoint = Just '.', asdigitgroups = Nothing}, amultiplier=False}
|
||||
in
|
||||
tests "multiBalanceReport" [
|
||||
test "null journal" $
|
||||
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
|
||||
|
||||
,test "with -H on a populated period" $
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "a valid history on an empty period" $
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
|
||||
,test "a valid history on an empty period (more complex)" $
|
||||
(defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||
(
|
||||
[
|
||||
("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("assets:bank:saving","saving",3, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=1}])
|
||||
,("assets:cash","cash",2, [mamountp' "$-2.00"], mamountp' "$-2.00",Mixed [amount0 {aquantity=(-2)}])
|
||||
,("expenses:food","food",2, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=(1)}])
|
||||
,("expenses:supplies","supplies",2, [mamountp' "$1.00"], mamountp' "$1.00",Mixed [amount0 {aquantity=(1)}])
|
||||
,("income:gifts","gifts",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
,("income:salary","salary",2, [mamountp' "$-1.00"], mamountp' "$-1.00",Mixed [amount0 {aquantity=(-1)}])
|
||||
],
|
||||
Mixed [usd0])
|
||||
]
|
||||
]
|
||||
|
@ -12,7 +12,7 @@ module Hledger.Reports.PostingsReport (
|
||||
mkpostingsReportItem,
|
||||
|
||||
-- * Tests
|
||||
tests_Hledger_Reports_PostingsReport
|
||||
easytests_PostingsReport
|
||||
)
|
||||
where
|
||||
|
||||
@ -26,7 +26,7 @@ import Safe (headMay, lastMay)
|
||||
|
||||
import Hledger.Data
|
||||
import Hledger.Query
|
||||
import Hledger.Utils
|
||||
import Hledger.Utils hiding (is)
|
||||
import Hledger.Reports.ReportOptions
|
||||
|
||||
|
||||
@ -174,11 +174,6 @@ summarisePostingsByInterval interval wd depth showempty reportspan ps = concatMa
|
||||
summarisespan s = summarisePostingsInDateSpan s wd depth showempty (postingsinspan s)
|
||||
postingsinspan s = filter (isPostingInDateSpan' wd s) ps
|
||||
|
||||
tests_summarisePostingsByInterval = [
|
||||
"summarisePostingsByInterval" ~: do
|
||||
summarisePostingsByInterval (Quarters 1) PrimaryDate 99999 False (DateSpan Nothing Nothing) [] ~?= []
|
||||
]
|
||||
|
||||
-- | A summary posting summarises the activity in one account within a report
|
||||
-- interval. It is currently kludgily represented by a regular Posting with no
|
||||
-- description, the interval's start date stored as the posting date, and the
|
||||
@ -220,209 +215,217 @@ summarisePostingsInDateSpan (DateSpan b e) wd depth showempty ps
|
||||
bal = if isclipped a then aibalance else aebalance
|
||||
isclipped a = accountNameLevel a >= depth
|
||||
|
||||
-- tests_summarisePostingsInDateSpan = [
|
||||
-- "summarisePostingsInDateSpan" ~: do
|
||||
-- let gives (b,e,depth,showempty,ps) =
|
||||
-- (summarisePostingsInDateSpan (mkdatespan b e) depth showempty ps `is`)
|
||||
-- let ps =
|
||||
-- [
|
||||
-- nullposting{lpdescription="desc",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining", lpamount=Mixed [usd 2]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food", lpamount=Mixed [usd 4]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining", lpamount=Mixed [usd 8]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,9999,False,[]) `gives`
|
||||
-- []
|
||||
-- ("2008/01/01","2009/01/01",0,9999,True,[]) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31"}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,9999,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food", lpamount=Mixed [usd 4]}
|
||||
-- ,nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food:dining", lpamount=Mixed [usd 10]}
|
||||
-- ,nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,2,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,1,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,0,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
-- tests
|
||||
|
||||
tests_postingsReport = [
|
||||
"postingsReport" ~: do
|
||||
is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
|
||||
is = flip expectEq'
|
||||
|
||||
-- with the query specified explicitly
|
||||
let (query, journal) `gives` n = (length $ snd $ postingsReport defreportopts query journal) `is` n
|
||||
(Any, nulljournal) `gives` 0
|
||||
(Any, samplejournal) `gives` 13
|
||||
-- register --depth just clips account names
|
||||
(Depth 2, samplejournal) `gives` 13
|
||||
(And [Depth 1, StatusQ Cleared, Acct "expenses"], samplejournal) `gives` 2
|
||||
(And [And [Depth 1, StatusQ Cleared], Acct "expenses"], samplejournal) `gives` 2
|
||||
easytests_PostingsReport = tests "PostingsReport" [
|
||||
|
||||
-- with query and/or command-line options
|
||||
assertEqual "" 13 (length $ snd $ postingsReport defreportopts Any samplejournal)
|
||||
assertEqual "" 11 (length $ snd $ postingsReport defreportopts{interval_=Months 1} Any samplejournal)
|
||||
assertEqual "" 20 (length $ snd $ postingsReport defreportopts{interval_=Months 1, empty_=True} Any samplejournal)
|
||||
assertEqual "" 5 (length $ snd $ postingsReport defreportopts (Acct "assets:bank:checking") samplejournal)
|
||||
tests "postingsReport" $
|
||||
let (query, journal) `gives` n = (length $ snd $ postingsReport defreportopts query journal) `is` n
|
||||
in [
|
||||
-- with the query specified explicitly
|
||||
(Any, nulljournal) `gives` 0
|
||||
,(Any, samplejournal) `gives` 13
|
||||
-- register --depth just clips account names
|
||||
,(Depth 2, samplejournal) `gives` 13
|
||||
,(And [Depth 1, StatusQ Cleared, Acct "expenses"], samplejournal) `gives` 2
|
||||
,(And [And [Depth 1, StatusQ Cleared], Acct "expenses"], samplejournal) `gives` 2
|
||||
|
||||
-- with query and/or command-line options
|
||||
,(length $ snd $ postingsReport defreportopts Any samplejournal) `is` 13
|
||||
,(length $ snd $ postingsReport defreportopts{interval_=Months 1} Any samplejournal) `is` 11
|
||||
,(length $ snd $ postingsReport defreportopts{interval_=Months 1, empty_=True} Any samplejournal) `is` 20
|
||||
,(length $ snd $ postingsReport defreportopts (Acct "assets:bank:checking") samplejournal) `is` 5
|
||||
|
||||
-- (defreportopts, And [Acct "a a", Acct "'b"], samplejournal2) `gives` 0
|
||||
-- [(Just (parsedate "2008-01-01","income"),assets:bank:checking $1,$1)
|
||||
-- ,(Nothing,income:salary $-1,0)
|
||||
-- ,(Just (2008-06-01,"gift"),assets:bank:checking $1,$1)
|
||||
-- ,(Nothing,income:gifts $-1,0)
|
||||
-- ,(Just (2008-06-02,"save"),assets:bank:saving $1,$1)
|
||||
-- ,(Nothing,assets:bank:checking $-1,0)
|
||||
-- ,(Just (2008-06-03,"eat & shop"),expenses:food $1,$1)
|
||||
-- ,(Nothing,expenses:supplies $1,$2)
|
||||
-- ,(Nothing,assets:cash $-2,0)
|
||||
-- ,(Just (2008-12-31,"pay off"),liabilities:debts $1,$1)
|
||||
-- ,(Nothing,assets:bank:checking $-1,0)
|
||||
|
||||
-- (defreportopts, And [Acct "a a", Acct "'b"], samplejournal2) `gives` 0
|
||||
-- [(Just (parsedate "2008-01-01","income"),assets:bank:checking $1,$1)
|
||||
-- ,(Nothing,income:salary $-1,0)
|
||||
-- ,(Just (2008-06-01,"gift"),assets:bank:checking $1,$1)
|
||||
-- ,(Nothing,income:gifts $-1,0)
|
||||
-- ,(Just (2008-06-02,"save"),assets:bank:saving $1,$1)
|
||||
-- ,(Nothing,assets:bank:checking $-1,0)
|
||||
-- ,(Just (2008-06-03,"eat & shop"),expenses:food $1,$1)
|
||||
-- ,(Nothing,expenses:supplies $1,$2)
|
||||
-- ,(Nothing,assets:cash $-2,0)
|
||||
-- ,(Just (2008-12-31,"pay off"),liabilities:debts $1,$1)
|
||||
-- ,(Nothing,assets:bank:checking $-1,0)
|
||||
-- ]
|
||||
{-
|
||||
let opts = defreportopts
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank:saving $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
,"2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report with cleared option" ~:
|
||||
do
|
||||
let opts = defreportopts{cleared_=True}
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report with uncleared option" ~:
|
||||
do
|
||||
let opts = defreportopts{uncleared_=True}
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank:saving $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report sorts by date" ~:
|
||||
do
|
||||
j <- readJournal' $ unlines
|
||||
["2008/02/02 a"
|
||||
," b 1"
|
||||
," c"
|
||||
,""
|
||||
,"2008/01/01 d"
|
||||
," e 1"
|
||||
," f"
|
||||
]
|
||||
let opts = defreportopts
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/02/02"]
|
||||
|
||||
,"postings report with account pattern" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{patterns_=["cash"]}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"postings report with account pattern, case insensitive" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{patterns_=["cAsH"]}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"postings report with display expression" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let gives displayexpr =
|
||||
(registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is`)
|
||||
where opts = defreportopts{display_=Just displayexpr}
|
||||
"d<[2008/6/2]" `gives` ["2008/01/01","2008/06/01"]
|
||||
"d<=[2008/6/2]" `gives` ["2008/01/01","2008/06/01","2008/06/02"]
|
||||
"d=[2008/6/2]" `gives` ["2008/06/02"]
|
||||
"d>=[2008/6/2]" `gives` ["2008/06/02","2008/06/03","2008/12/31"]
|
||||
"d>[2008/6/2]" `gives` ["2008/06/03","2008/12/31"]
|
||||
|
||||
,"postings report with period expression" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let periodexpr `gives` dates = do
|
||||
j' <- samplejournal
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j') `is` dates
|
||||
where opts = defreportopts{period_=maybePeriod date1 periodexpr}
|
||||
"" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
"2008" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
"2007" `gives` []
|
||||
"june" `gives` ["2008/06/01","2008/06/02","2008/06/03"]
|
||||
"monthly" `gives` ["2008/01/01","2008/06/01","2008/12/01"]
|
||||
"quarterly" `gives` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "yearly"}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 - 2008/12/31 assets:bank:saving $1 $1"
|
||||
," assets:cash $-2 $-1"
|
||||
," expenses:food $1 0"
|
||||
," expenses:supplies $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
," income:salary $-1 $-1"
|
||||
," liabilities:debts $1 0"
|
||||
]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "quarterly"}
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "quarterly",empty_=True}
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/07/01","2008/10/01"]
|
||||
|
||||
]
|
||||
|
||||
, "postings report with depth arg" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{depth_=Just 2}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank $1 $1"
|
||||
," assets:bank $-1 0"
|
||||
,"2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank $-1 0"
|
||||
]
|
||||
|
||||
-}
|
||||
]
|
||||
|
||||
{-
|
||||
let opts = defreportopts
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank:saving $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
,"2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report with cleared option" ~:
|
||||
do
|
||||
let opts = defreportopts{cleared_=True}
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report with uncleared option" ~:
|
||||
do
|
||||
let opts = defreportopts{uncleared_=True}
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank:saving $1 $1"
|
||||
," assets:bank:checking $-1 0"
|
||||
]
|
||||
|
||||
,"postings report sorts by date" ~:
|
||||
do
|
||||
j <- readJournal' $ unlines
|
||||
["2008/02/02 a"
|
||||
," b 1"
|
||||
," c"
|
||||
,""
|
||||
,"2008/01/01 d"
|
||||
," e 1"
|
||||
," f"
|
||||
]
|
||||
let opts = defreportopts
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/02/02"]
|
||||
|
||||
,"postings report with account pattern" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{patterns_=["cash"]}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"postings report with account pattern, case insensitive" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{patterns_=["cAsH"]}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"postings report with display expression" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let gives displayexpr =
|
||||
(registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is`)
|
||||
where opts = defreportopts{display_=Just displayexpr}
|
||||
"d<[2008/6/2]" `gives` ["2008/01/01","2008/06/01"]
|
||||
"d<=[2008/6/2]" `gives` ["2008/01/01","2008/06/01","2008/06/02"]
|
||||
"d=[2008/6/2]" `gives` ["2008/06/02"]
|
||||
"d>=[2008/6/2]" `gives` ["2008/06/02","2008/06/03","2008/12/31"]
|
||||
"d>[2008/6/2]" `gives` ["2008/06/03","2008/12/31"]
|
||||
|
||||
,"postings report with period expression" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let periodexpr `gives` dates = do
|
||||
j' <- samplejournal
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j') `is` dates
|
||||
where opts = defreportopts{period_=maybePeriod date1 periodexpr}
|
||||
"" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
"2008" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
"2007" `gives` []
|
||||
"june" `gives` ["2008/06/01","2008/06/02","2008/06/03"]
|
||||
"monthly" `gives` ["2008/01/01","2008/06/01","2008/12/01"]
|
||||
"quarterly" `gives` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "yearly"}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 - 2008/12/31 assets:bank:saving $1 $1"
|
||||
," assets:cash $-2 $-1"
|
||||
," expenses:food $1 0"
|
||||
," expenses:supplies $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
," income:salary $-1 $-1"
|
||||
," liabilities:debts $1 0"
|
||||
]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "quarterly"}
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = defreportopts{period_=maybePeriod date1 "quarterly",empty_=True}
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/07/01","2008/10/01"]
|
||||
|
||||
]
|
||||
|
||||
, "postings report with depth arg" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = defreportopts{depth_=Just 2}
|
||||
(postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
|
||||
["2008/01/01 income assets:bank $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank $1 $1"
|
||||
," income:gifts $-1 0"
|
||||
,"2008/06/02 save assets:bank $1 $1"
|
||||
," assets:bank $-1 0"
|
||||
,"2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
,"2008/12/31 pay off liabilities:debts $1 $1"
|
||||
," assets:bank $-1 0"
|
||||
]
|
||||
|
||||
-}
|
||||
,tests "summarisePostingsByInterval" [
|
||||
tests "summarisePostingsByInterval" [
|
||||
summarisePostingsByInterval (Quarters 1) PrimaryDate 99999 False (DateSpan Nothing Nothing) [] `is` []
|
||||
]
|
||||
]
|
||||
|
||||
-- ,tests_summarisePostingsInDateSpan = [
|
||||
-- "summarisePostingsInDateSpan" ~: do
|
||||
-- let gives (b,e,depth,showempty,ps) =
|
||||
-- (summarisePostingsInDateSpan (mkdatespan b e) depth showempty ps `is`)
|
||||
-- let ps =
|
||||
-- [
|
||||
-- nullposting{lpdescription="desc",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining", lpamount=Mixed [usd 2]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food", lpamount=Mixed [usd 4]}
|
||||
-- ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining", lpamount=Mixed [usd 8]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,9999,False,[]) `gives`
|
||||
-- []
|
||||
-- ("2008/01/01","2009/01/01",0,9999,True,[]) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31"}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,9999,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food", lpamount=Mixed [usd 4]}
|
||||
-- ,nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food:dining", lpamount=Mixed [usd 10]}
|
||||
-- ,nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,2,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses:food",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,1,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="expenses",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
-- ("2008/01/01","2009/01/01",0,0,False,ts) `gives`
|
||||
-- [
|
||||
-- nullposting{lpdate=parsedate "2008/01/01",lpdescription="- 2008/12/31",lpaccount="",lpamount=Mixed [usd 15]}
|
||||
-- ]
|
||||
|
||||
]
|
||||
|
||||
tests_Hledger_Reports_PostingsReport = TestList $
|
||||
tests_summarisePostingsByInterval
|
||||
++ tests_postingsReport
|
||||
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
||||
{-|
|
||||
|
||||
Here are several variants of a transactions report.
|
||||
@ -22,7 +22,8 @@ module Hledger.Reports.TransactionsReports (
|
||||
journalTransactionsReport,
|
||||
accountTransactionsReport,
|
||||
transactionsReportByCommodity,
|
||||
transactionRegisterDate
|
||||
transactionRegisterDate,
|
||||
easytests_TransactionsReports
|
||||
)
|
||||
where
|
||||
|
||||
@ -35,7 +36,7 @@ import Data.Time.Calendar
|
||||
import Hledger.Data
|
||||
import Hledger.Query
|
||||
import Hledger.Reports.ReportOptions
|
||||
import Hledger.Utils.Debug
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
-- | A transactions report includes a list of transactions
|
||||
@ -275,3 +276,7 @@ filterTransactionsReportByCommodity c (label,items) =
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- tests
|
||||
|
||||
easytests_TransactionsReports = tests "TransactionsReports" [
|
||||
]
|
||||
|
Loading…
Reference in New Issue
Block a user