focus on tests in Tests.hs, clean up

This commit is contained in:
Simon Michael 2008-10-15 06:32:52 +00:00
parent 7a69efec70
commit 1e3291af48
14 changed files with 63 additions and 116 deletions

View File

@ -13,9 +13,6 @@ import Ledger.Types
import Ledger.Amount import Ledger.Amount
accounttests = TestList [
]
instance Show Account where instance Show Account where
show (Account a ts b) = printf "Account %s with %d txns and %s balance" a (length ts) (show b) show (Account a ts b) = printf "Account %s with %d txns and %s balance" a (length ts) (show b)

View File

@ -11,9 +11,6 @@ import Ledger.Utils
import Ledger.Types import Ledger.Types
accountnametests = TestList [
]
sepchar = ':' sepchar = ':'
accountNameComponents :: AccountName -> [String] accountNameComponents :: AccountName -> [String]

View File

@ -43,9 +43,6 @@ import Ledger.Types
import Ledger.Commodity import Ledger.Commodity
amounttests = TestList [
]
instance Show Amount where show = showAmount instance Show Amount where show = showAmount
-- | Get the string representation of an amount, based on its commodity's -- | Get the string representation of an amount, based on its commodity's

View File

@ -13,9 +13,6 @@ import Ledger.Utils
import Ledger.Types import Ledger.Types
commoditytests = TestList [
]
-- for nullamt, autoamt, etc. -- for nullamt, autoamt, etc.
unknown = Commodity {symbol="",side=L,spaced=False,comma=False,precision=0,rate=1} unknown = Commodity {symbol="",side=L,spaced=False,comma=False,precision=0,rate=1}

View File

@ -13,9 +13,6 @@ import Ledger.RawTransaction
import Ledger.Amount import Ledger.Amount
entrytests = TestList [
]
instance Show Entry where show = showEntryDescription instance Show Entry where show = showEntryDescription
{- {-

View File

@ -19,9 +19,6 @@ import Ledger.RawLedger
import Ledger.Entry import Ledger.Entry
ledgertests = TestList [
]
instance Show Ledger where instance Show Ledger where
show l = printf "Ledger with %d entries, %d accounts\n%s" show l = printf "Ledger with %d entries, %d accounts\n%s"
((length $ entries $ rawledger l) + ((length $ entries $ rawledger l) +

View File

@ -21,9 +21,6 @@ import Ledger.Commodity
import Ledger.TimeLog import Ledger.TimeLog
parsertests = TestList [
]
-- utils -- utils
parseLedgerFile :: String -> IO (Either ParseError RawLedger) parseLedgerFile :: String -> IO (Either ParseError RawLedger)

View File

@ -15,9 +15,6 @@ import Ledger.Entry
import Ledger.Transaction import Ledger.Transaction
rawledgertests = TestList [
]
instance Show RawLedger where instance Show RawLedger where
show l = printf "RawLedger with %d entries, %d accounts: %s" show l = printf "RawLedger with %d entries, %d accounts: %s"
((length $ entries l) + ((length $ entries l) +

View File

@ -12,9 +12,6 @@ import Ledger.Types
import Ledger.Amount import Ledger.Amount
rawtransactiontests = TestList [
]
instance Show RawTransaction where show = showLedgerTransaction instance Show RawTransaction where show = showLedgerTransaction
showLedgerTransaction :: RawTransaction -> String showLedgerTransaction :: RawTransaction -> String

View File

@ -14,9 +14,6 @@ import Ledger.Commodity
import Ledger.Amount import Ledger.Amount
timelogtests = TestList [
]
instance Show TimeLogEntry where instance Show TimeLogEntry where
show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t) show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t)

View File

@ -14,9 +14,6 @@ import Ledger.RawTransaction
import Ledger.Amount import Ledger.Amount
transactiontests = TestList [
]
instance Show Transaction where instance Show Transaction where
show (Transaction eno d desc a amt) = show (Transaction eno d desc a amt) =
unwords [d,desc,a,show amt] unwords [d,desc,a,show amt]

View File

@ -10,9 +10,6 @@ import Ledger
import Options import Options
printcommandtests = TestList [
]
-- | Print ledger entries in standard format. -- | Print ledger entries in standard format.
print' :: [Opt] -> [String] -> Ledger -> IO () print' :: [Opt] -> [String] -> Ledger -> IO ()
print' opts args l = putStr $ showEntries opts args l print' opts args l = putStr $ showEntries opts args l

View File

@ -10,9 +10,6 @@ import Ledger
import Options import Options
registercommandtests = TestList [
]
-- | Print a register report. -- | Print a register report.
register :: [Opt] -> [String] -> Ledger -> IO () register :: [Opt] -> [String] -> Ledger -> IO ()
register opts args l = putStr $ showTransactionsWithBalances opts args l register opts args l = putStr $ showTransactionsWithBalances opts args l

140
Tests.hs
View File

@ -15,80 +15,71 @@ import RegisterCommand
-- quickcheck = mapM quickCheck ([ -- quickcheck = mapM quickCheck ([
-- ] :: [Bool]) -- ] :: [Bool])
runtests = runTestTT alltests runtests = runTestTT $ tconcat [unittests, functests]
alltests = concattests [ tconcat :: [Test] -> Test
tests tconcat = foldr (\(TestList as) (TestList bs) -> TestList (as ++ bs)) (TestList [])
,accounttests
,accountnametests
,amounttests
,balancecommandtests
,commoditytests
,entrytests
,ledgertests
,parsertests
,printcommandtests
,rawledgertests
,rawtransactiontests
,registercommandtests
,timelogtests
]
where
concattests = foldr (\(TestList as) (TestList bs) -> TestList (as ++ bs)) (TestList [])
tests = ------------------------------------------------------------------------------
TestList unittests = TestList
-- NB assertequal arguments on a new line have to be indented at least
-- one space, contrary to haskell-mode's auto indent
[ [
"display dollar amount" ~: show (dollars 1) ~?= "$1.00" "show dollars" ~: show (dollars 1) ~?= "$1.00"
,"display time amount" ~: show (hours 1) ~?= "1.0h" ,"show hours" ~: show (hours 1) ~?= "1.0h"
-- ,"amount precision" ~: do ,"amount arithmetic" ~: do
-- let a1 = dollars 1.23 let a1 = dollars 1.23
-- let a2 = Amount (comm "$") (-1.23) 2 let a2 = Amount (comm "$") (-1.23)
-- let a3 = Amount (comm "$") (-1.23) 3 let a3 = Amount (comm "$") (-1.23)
-- assertequal (Amount (comm "$") 0 1) (a1 + a2) assertequal (Amount (comm "$") 0) (a1 + a2)
-- assertequal (Amount (comm "$") 0 1) (a1 + a3) assertequal (Amount (comm "$") 0) (a1 + a3)
-- assertequal (Amount (comm "$") (-2.46) 2) (a2 + a3) assertequal (Amount (comm "$") (-2.46)) (a2 + a3)
-- assertequal (Amount (comm "$") (-2.46) 3) (a3 + a3) assertequal (Amount (comm "$") (-2.46)) (a3 + a3)
-- -- sum adds 0, with Amount fromIntegral's default precision of 2 assertequal (Amount (comm "$") (-2.46)) (sum [a2,a3])
-- assertequal (Amount (comm "$") 0 1) (sum [a1,a2]) assertequal (Amount (comm "$") (-2.46)) (sum [a3,a3])
-- assertequal (Amount (comm "$") (-2.46) 2) (sum [a2,a3]) assertequal (Amount (comm "$") 0) (sum [a1,a2,a3,-a3])
-- assertequal (Amount (comm "$") (-2.46) 2) (sum [a3,a3])
,"ledgertransaction" ~: do ,"ledgertransaction" ~: do
assertparseequal rawtransaction1 (parsewith ledgertransaction rawtransaction1_str) assertparseequal rawtransaction1 (parsewith ledgertransaction rawtransaction1_str)
,"ledgerentry" ~: do
assertparseequal entry1 (parsewith ledgerentry entry1_str)
,"ledgerentry" ~: do ,"autofillEntry" ~: do
assertparseequal entry1 (parsewith ledgerentry entry1_str) assertequal
(dollars (-47.18))
(tamount $ last $ etransactions $ autofillEntry entry1)
,"punctuatethousands" ~: punctuatethousands "" @?= ""
,"punctuatethousands" ~: punctuatethousands "1234567.8901" @?= "1,234,567.8901"
,"punctuatethousands" ~: punctuatethousands "-100" @?= "-100"
,"autofillEntry" ~: do ,"expandAccountNames" ~: do
assertequal assertequal
(dollars (-47.18)) ["assets","assets:cash","assets:checking","expenses","expenses:vacation"]
(tamount $ last $ etransactions $ autofillEntry entry1) (expandAccountNames ["assets:cash","assets:checking","expenses:vacation"])
,"punctuatethousands" ~: punctuatethousands "" @?= "" ,"ledgerAccountNames" ~: do
,"punctuatethousands" ~: punctuatethousands "1234567.8901" @?= "1,234,567.8901" assertequal
,"punctuatethousands" ~: punctuatethousands "-100" @?= "-100" ["assets","assets:cash","assets:checking","assets:saving","equity","equity:opening balances",
"expenses","expenses:food","expenses:food:dining","expenses:phone","expenses:vacation",
"liabilities","liabilities:credit cards","liabilities:credit cards:discover"]
(accountnames ledger7)
,"expandAccountNames" ~: do ,"cacheLedger" ~: do
assertequal assertequal 15 (length $ Map.keys $ accountmap $ cacheLedger rawledger7 )
["assets","assets:cash","assets:checking","expenses","expenses:vacation"]
(expandAccountNames ["assets:cash","assets:checking","expenses:vacation"])
,"ledgerAccountNames" ~: do ,"transactionamount" ~: do
assertequal assertparseequal (dollars 47.18) (parsewith transactionamount " $47.18")
["assets","assets:cash","assets:checking","assets:saving","equity","equity:opening balances", assertparseequal (Amount (Commodity {symbol="$",side=L,spaced=False,comma=False,precision=0,rate=1}) 1) (parsewith transactionamount " $1.")
"expenses","expenses:food","expenses:food:dining","expenses:phone","expenses:vacation", ]
"liabilities","liabilities:credit cards","liabilities:credit cards:discover"]
(accountnames ledger7)
,"cacheLedger" ~: do ------------------------------------------------------------------------------
assertequal 15 (length $ Map.keys $ accountmap $ cacheLedger rawledger7 ) functests = TestList
[
,"transactionamount" ~: do balancecommandtests
assertparseequal (dollars 47.18) (parsewith transactionamount " $47.18")
assertparseequal (Amount (Commodity {symbol="$",side=L,spaced=False,comma=False,precision=0,rate=1}) 1) (parsewith transactionamount " $1.")
] ]
balancecommandtests = balancecommandtests =
@ -103,8 +94,7 @@ balancecommandtests =
\ $1 liabilities\n\ \ $1 liabilities\n\
\" --" \" --"
(showBalanceReport [] [] l) (showBalanceReport [] [] l)
, ,
"balance report with showsubs" ~: do "balance report with showsubs" ~: do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
@ -120,8 +110,7 @@ balancecommandtests =
\ $1 liabilities:debts\n\ \ $1 liabilities:debts\n\
\" --" \" --"
(showBalanceReport [ShowSubs] [] l) (showBalanceReport [ShowSubs] [] l)
, ,
"balance report with account pattern o" ~: do "balance report with account pattern o" ~: do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
@ -131,8 +120,7 @@ balancecommandtests =
\ $-1\n\ \ $-1\n\
\" --" \" --"
(showBalanceReport [] ["o"] l) (showBalanceReport [] ["o"] l)
, ,
"balance report with account pattern o and showsubs" ~: do "balance report with account pattern o and showsubs" ~: do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
@ -144,8 +132,7 @@ balancecommandtests =
\ $-1\n\ \ $-1\n\
\" --" \" --"
(showBalanceReport [ShowSubs] ["o"] l) (showBalanceReport [ShowSubs] ["o"] l)
, ,
"balance report with account pattern a" ~: do "balance report with account pattern a" ~: do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
@ -158,8 +145,7 @@ balancecommandtests =
\ $-1\n\ \ $-1\n\
\" --" \" --"
(showBalanceReport [] ["a"] l) (showBalanceReport [] ["a"] l)
, ,
"balance report with account pattern e" ~: do "balance report with account pattern e" ~: do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
@ -170,9 +156,9 @@ balancecommandtests =
\ $1 liabilities:debts\n\ \ $1 liabilities:debts\n\
\" --" \" --"
(showBalanceReport [] ["e"] l) (showBalanceReport [] ["e"] l)
, ,
"balance report with unmatched parent of two matched subaccounts" ~:
"balance report with unmatched parent of two matched subaccounts" ~: do do
l <- ledgerfromfile "sample.ledger" l <- ledgerfromfile "sample.ledger"
assertequal assertequal
" $-2 assets:cash\n\ " $-2 assets:cash\n\
@ -197,8 +183,8 @@ balancecommandtests =
assertparseequal :: (Show a, Eq a) => a -> (Either ParseError a) -> Assertion assertparseequal :: (Show a, Eq a) => a -> (Either ParseError a) -> Assertion
assertparseequal expected parsed = either printParseError (assertequal expected) parsed assertparseequal expected parsed = either printParseError (assertequal expected) parsed
------------------------------------------------------------------------------
-- test data -- data
rawtransaction1_str = " expenses:food:dining $10.00\n" rawtransaction1_str = " expenses:food:dining $10.00\n"