rename easytests_* to tests_*
This commit is contained in:
parent
f388d9311a
commit
91b111b60d
@ -2,7 +2,7 @@
|
|||||||
|
|
||||||
module Hledger (
|
module Hledger (
|
||||||
module X
|
module X
|
||||||
,easytests_Hledger
|
,tests_Hledger
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -12,10 +12,10 @@ import Hledger.Reports as X
|
|||||||
import Hledger.Query as X
|
import Hledger.Query as X
|
||||||
import Hledger.Utils as X
|
import Hledger.Utils as X
|
||||||
|
|
||||||
easytests_Hledger = tests "Hledger" [
|
tests_Hledger = tests "Hledger" [
|
||||||
easytests_Data
|
tests_Data
|
||||||
,easytests_Query
|
,tests_Query
|
||||||
,easytests_Read
|
,tests_Read
|
||||||
,easytests_Reports
|
,tests_Reports
|
||||||
,easytests_Utils
|
,tests_Utils
|
||||||
]
|
]
|
||||||
|
|||||||
@ -26,7 +26,7 @@ module Hledger.Data (
|
|||||||
module Hledger.Data.Transaction,
|
module Hledger.Data.Transaction,
|
||||||
module Hledger.Data.TransactionModifier,
|
module Hledger.Data.TransactionModifier,
|
||||||
module Hledger.Data.Types,
|
module Hledger.Data.Types,
|
||||||
easytests_Data
|
tests_Data
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -49,13 +49,13 @@ import Hledger.Data.TransactionModifier
|
|||||||
import Hledger.Data.Types
|
import Hledger.Data.Types
|
||||||
import Hledger.Utils.Test
|
import Hledger.Utils.Test
|
||||||
|
|
||||||
easytests_Data = tests "Data" [
|
tests_Data = tests "Data" [
|
||||||
easytests_AccountName
|
tests_AccountName
|
||||||
,easytests_Amount
|
,tests_Amount
|
||||||
,easytests_Journal
|
,tests_Journal
|
||||||
,easytests_Ledger
|
,tests_Ledger
|
||||||
,easytests_Posting
|
,tests_Posting
|
||||||
,easytests_StringFormat
|
,tests_StringFormat
|
||||||
,easytests_Timeclock
|
,tests_Timeclock
|
||||||
,easytests_Transaction
|
,tests_Transaction
|
||||||
]
|
]
|
||||||
|
|||||||
@ -36,7 +36,7 @@ module Hledger.Data.AccountName (
|
|||||||
,subAccountNamesFrom
|
,subAccountNamesFrom
|
||||||
,topAccountNames
|
,topAccountNames
|
||||||
,unbudgetedAccountName
|
,unbudgetedAccountName
|
||||||
,easytests_AccountName
|
,tests_AccountName
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -226,7 +226,7 @@ accountRegexToAccountName = T.pack . regexReplace "^\\^(.*?)\\(:\\|\\$\\)$" "\\1
|
|||||||
--isAccountRegex :: String -> Bool
|
--isAccountRegex :: String -> Bool
|
||||||
--isAccountRegex s = take 1 s == "^" && take 5 (reverse s) == ")$|:("
|
--isAccountRegex s = take 1 s == "^" && take 5 (reverse s) == ")$|:("
|
||||||
|
|
||||||
easytests_AccountName = tests "AccountName" [
|
tests_AccountName = tests "AccountName" [
|
||||||
tests "accountNameTreeFrom" [
|
tests "accountNameTreeFrom" [
|
||||||
accountNameTreeFrom ["a"] `is` Node "root" [Node "a" []]
|
accountNameTreeFrom ["a"] `is` Node "root" [Node "a" []]
|
||||||
,accountNameTreeFrom ["a","b"] `is` Node "root" [Node "a" [], Node "b" []]
|
,accountNameTreeFrom ["a","b"] `is` Node "root" [Node "a" [], Node "b" []]
|
||||||
|
|||||||
@ -114,7 +114,7 @@ module Hledger.Data.Amount (
|
|||||||
canonicaliseMixedAmount,
|
canonicaliseMixedAmount,
|
||||||
-- * misc.
|
-- * misc.
|
||||||
ltraceamount,
|
ltraceamount,
|
||||||
easytests_Amount
|
tests_Amount
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
@ -671,7 +671,7 @@ mixedAmountValue j d (Mixed as) = Mixed $ map (amountValue j d) as
|
|||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Amount = tests "Amount" [
|
tests_Amount = tests "Amount" [
|
||||||
tests "Amount" [
|
tests "Amount" [
|
||||||
|
|
||||||
tests "costOfAmount" [
|
tests "costOfAmount" [
|
||||||
|
|||||||
@ -68,7 +68,7 @@ module Hledger.Data.Journal (
|
|||||||
journalUntieTransactions,
|
journalUntieTransactions,
|
||||||
-- * Tests
|
-- * Tests
|
||||||
samplejournal,
|
samplejournal,
|
||||||
easytests_Journal,
|
tests_Journal,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
import Control.Applicative (Const(..))
|
import Control.Applicative (Const(..))
|
||||||
@ -1060,7 +1060,7 @@ Right samplejournal = journalBalanceTransactions False $
|
|||||||
]
|
]
|
||||||
}
|
}
|
||||||
|
|
||||||
easytests_Journal = tests "Journal" [
|
tests_Journal = tests "Journal" [
|
||||||
|
|
||||||
test "journalDateSpan" $
|
test "journalDateSpan" $
|
||||||
journalDateSpan True nulljournal{
|
journalDateSpan True nulljournal{
|
||||||
|
|||||||
@ -21,7 +21,7 @@ module Hledger.Data.Ledger (
|
|||||||
,ledgerPostings
|
,ledgerPostings
|
||||||
,ledgerDateSpan
|
,ledgerDateSpan
|
||||||
,ledgerCommodities
|
,ledgerCommodities
|
||||||
,easytests_Ledger
|
,tests_Ledger
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -107,7 +107,7 @@ ledgerCommodities = M.keys . jinferredcommodities . ljournal
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Ledger = tests "Ledger" [
|
tests_Ledger = tests "Ledger" [
|
||||||
|
|
||||||
tests "ledgerFromJournal" [
|
tests "ledgerFromJournal" [
|
||||||
(length $ ledgerPostings $ ledgerFromJournal Any nulljournal) `is` 0
|
(length $ ledgerPostings $ ledgerFromJournal Any nulljournal) `is` 0
|
||||||
|
|||||||
@ -54,7 +54,7 @@ module Hledger.Data.Posting (
|
|||||||
showPosting,
|
showPosting,
|
||||||
-- * misc.
|
-- * misc.
|
||||||
showComment,
|
showComment,
|
||||||
easytests_Posting
|
tests_Posting
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
import Data.List
|
import Data.List
|
||||||
@ -293,7 +293,7 @@ aliasReplace (RegexAlias re repl) a = T.pack $ regexReplaceCIMemo re repl $ T.un
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Posting = tests "Posting" [
|
tests_Posting = tests "Posting" [
|
||||||
|
|
||||||
tests "accountNamePostingType" [
|
tests "accountNamePostingType" [
|
||||||
accountNamePostingType "a" `is` RegularPosting
|
accountNamePostingType "a" `is` RegularPosting
|
||||||
|
|||||||
@ -10,7 +10,7 @@ module Hledger.Data.StringFormat (
|
|||||||
, StringFormat(..)
|
, StringFormat(..)
|
||||||
, StringFormatComponent(..)
|
, StringFormatComponent(..)
|
||||||
, ReportItemField(..)
|
, ReportItemField(..)
|
||||||
, easytests_StringFormat
|
, tests_StringFormat
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
@ -143,7 +143,7 @@ formatStringTester fs value expected = actual `is` expected
|
|||||||
FormatLiteral l -> formatString False Nothing Nothing l
|
FormatLiteral l -> formatString False Nothing Nothing l
|
||||||
FormatField leftJustify min max _ -> formatString leftJustify min max value
|
FormatField leftJustify min max _ -> formatString leftJustify min max value
|
||||||
|
|
||||||
easytests_StringFormat = tests "StringFormat" [
|
tests_StringFormat = tests "StringFormat" [
|
||||||
|
|
||||||
tests "formatStringHelper" [
|
tests "formatStringHelper" [
|
||||||
formatStringTester (FormatLiteral " ") "" " "
|
formatStringTester (FormatLiteral " ") "" " "
|
||||||
|
|||||||
@ -10,7 +10,7 @@ converted to 'Transactions' and queried like a ledger.
|
|||||||
|
|
||||||
module Hledger.Data.Timeclock (
|
module Hledger.Data.Timeclock (
|
||||||
timeclockEntriesToTransactions
|
timeclockEntriesToTransactions
|
||||||
,easytests_Timeclock
|
,tests_Timeclock
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -113,7 +113,7 @@ entryFromTimeclockInOut i o
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Timeclock = tests "Timeclock" [
|
tests_Timeclock = tests "Timeclock" [
|
||||||
do
|
do
|
||||||
today <- io getCurrentDay
|
today <- io getCurrentDay
|
||||||
now' <- io getCurrentTime
|
now' <- io getCurrentTime
|
||||||
|
|||||||
@ -43,7 +43,7 @@ module Hledger.Data.Transaction (
|
|||||||
sourceFirstLine,
|
sourceFirstLine,
|
||||||
showGenericSourcePos,
|
showGenericSourcePos,
|
||||||
-- * tests
|
-- * tests
|
||||||
easytests_Transaction
|
tests_Transaction
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
import Data.List
|
import Data.List
|
||||||
@ -442,7 +442,7 @@ postingSetTransaction t p = p{ptransaction=Just t}
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Transaction = tests "Transaction" [
|
tests_Transaction = tests "Transaction" [
|
||||||
|
|
||||||
tests "showTransactionUnelided" [
|
tests "showTransactionUnelided" [
|
||||||
showTransactionUnelided nulltransaction `is` "0000/01/01\n\n"
|
showTransactionUnelided nulltransaction `is` "0000/01/01\n\n"
|
||||||
|
|||||||
@ -46,7 +46,7 @@ module Hledger.Query (
|
|||||||
matchesMarketPrice,
|
matchesMarketPrice,
|
||||||
words'',
|
words'',
|
||||||
-- * tests
|
-- * tests
|
||||||
easytests_Query
|
tests_Query
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -652,7 +652,7 @@ matchesMarketPrice _ _ = True
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Query = tests "Query" [
|
tests_Query = tests "Query" [
|
||||||
tests "simplifyQuery" [
|
tests "simplifyQuery" [
|
||||||
|
|
||||||
(simplifyQuery $ Or [Acct "a"]) `is` (Acct "a")
|
(simplifyQuery $ Or [Acct "a"]) `is` (Acct "a")
|
||||||
|
|||||||
@ -29,7 +29,7 @@ module Hledger.Read (
|
|||||||
module Hledger.Read.Common,
|
module Hledger.Read.Common,
|
||||||
|
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_Read,
|
tests_Read,
|
||||||
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
@ -307,10 +307,10 @@ tryReaders iopts mpath readers txt = firstSuccessOrFirstError [] readers
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Read = tests "Read" [
|
tests_Read = tests "Read" [
|
||||||
easytests_Common
|
tests_Common
|
||||||
,easytests_CsvReader
|
,tests_CsvReader
|
||||||
,easytests_JournalReader
|
,tests_JournalReader
|
||||||
]
|
]
|
||||||
|
|
||||||
--samplejournal = readJournal' $ T.unlines
|
--samplejournal = readJournal' $ T.unlines
|
||||||
|
|||||||
@ -92,7 +92,7 @@ module Hledger.Read.Common (
|
|||||||
singlespacep,
|
singlespacep,
|
||||||
|
|
||||||
-- * tests
|
-- * tests
|
||||||
easytests_Common,
|
tests_Common,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
--- * imports
|
--- * imports
|
||||||
@ -1200,7 +1200,7 @@ match' p = do
|
|||||||
|
|
||||||
--- * tests
|
--- * tests
|
||||||
|
|
||||||
easytests_Common = tests "Common" [
|
tests_Common = tests "Common" [
|
||||||
|
|
||||||
tests "amountp" [
|
tests "amountp" [
|
||||||
test "basic" $ expectParseEq amountp "$47.18" (usd 47.18)
|
test "basic" $ expectParseEq amountp "$47.18" (usd 47.18)
|
||||||
|
|||||||
@ -25,7 +25,7 @@ module Hledger.Read.CsvReader (
|
|||||||
expandIncludes,
|
expandIncludes,
|
||||||
transactionFromCsvRecord,
|
transactionFromCsvRecord,
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_CsvReader,
|
tests_CsvReader,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
@ -832,7 +832,7 @@ parseDateWithFormatOrDefaultFormats mformat s = firstJust $ map parsewith format
|
|||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_CsvReader = tests "CsvReader" [
|
tests_CsvReader = tests "CsvReader" [
|
||||||
tests "parseCsvRules" [
|
tests "parseCsvRules" [
|
||||||
test "empty file" $
|
test "empty file" $
|
||||||
parseCsvRules "unknown" "" `is` Right rules
|
parseCsvRules "unknown" "" `is` Right rules
|
||||||
|
|||||||
@ -58,7 +58,7 @@ module Hledger.Read.JournalReader (
|
|||||||
followingcommentp
|
followingcommentp
|
||||||
|
|
||||||
-- * Tests
|
-- * Tests
|
||||||
,easytests_JournalReader
|
,tests_JournalReader
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
--- * imports
|
--- * imports
|
||||||
@ -576,7 +576,7 @@ postingp mTransactionYear = do
|
|||||||
|
|
||||||
--- * tests
|
--- * tests
|
||||||
|
|
||||||
easytests_JournalReader = tests "JournalReader" [
|
tests_JournalReader = tests "JournalReader" [
|
||||||
|
|
||||||
let p = lift accountnamep :: JournalParser IO AccountName in
|
let p = lift accountnamep :: JournalParser IO AccountName in
|
||||||
tests "accountnamep" [
|
tests "accountnamep" [
|
||||||
|
|||||||
@ -19,7 +19,7 @@ module Hledger.Reports (
|
|||||||
module Hledger.Reports.BudgetReport,
|
module Hledger.Reports.BudgetReport,
|
||||||
-- module Hledger.Reports.BalanceHistoryReport,
|
-- module Hledger.Reports.BalanceHistoryReport,
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_Reports
|
tests_Reports
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -34,12 +34,12 @@ import Hledger.Reports.BudgetReport
|
|||||||
-- import Hledger.Reports.BalanceHistoryReport
|
-- import Hledger.Reports.BalanceHistoryReport
|
||||||
import Hledger.Utils.Test
|
import Hledger.Utils.Test
|
||||||
|
|
||||||
easytests_Reports = tests "Reports" [
|
tests_Reports = tests "Reports" [
|
||||||
easytests_BalanceReport
|
tests_BalanceReport
|
||||||
,easytests_BudgetReport
|
,tests_BudgetReport
|
||||||
,easytests_EntriesReport
|
,tests_EntriesReport
|
||||||
,easytests_MultiBalanceReports
|
,tests_MultiBalanceReports
|
||||||
,easytests_PostingsReport
|
,tests_PostingsReport
|
||||||
,easytests_ReportOptions
|
,tests_ReportOptions
|
||||||
,easytests_TransactionsReports
|
,tests_TransactionsReports
|
||||||
]
|
]
|
||||||
|
|||||||
@ -20,7 +20,7 @@ module Hledger.Reports.BalanceReport (
|
|||||||
flatShowsExclusiveBalance,
|
flatShowsExclusiveBalance,
|
||||||
|
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_BalanceReport
|
tests_BalanceReport
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -180,7 +180,7 @@ Right samplejournal2 =
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_BalanceReport = tests "BalanceReport" [
|
tests_BalanceReport = tests "BalanceReport" [
|
||||||
tests "balanceReport" $
|
tests "balanceReport" $
|
||||||
let
|
let
|
||||||
(opts,journal) `gives` r = do
|
(opts,journal) `gives` r = do
|
||||||
|
|||||||
@ -356,5 +356,5 @@ maybeAccountNameDrop opts a | flat_ opts = accountNameDrop (drop_ opts) a
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_BudgetReport = tests "BudgetReport" [
|
tests_BudgetReport = tests "BudgetReport" [
|
||||||
]
|
]
|
||||||
|
|||||||
@ -10,7 +10,7 @@ module Hledger.Reports.EntriesReport (
|
|||||||
EntriesReportItem,
|
EntriesReportItem,
|
||||||
entriesReport,
|
entriesReport,
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_EntriesReport
|
tests_EntriesReport
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -37,7 +37,7 @@ entriesReport opts q j =
|
|||||||
date = transactionDateFn opts
|
date = transactionDateFn opts
|
||||||
ts = jtxns $ journalSelectingAmountFromOpts opts j
|
ts = jtxns $ journalSelectingAmountFromOpts opts j
|
||||||
|
|
||||||
easytests_EntriesReport = tests "EntriesReport" [
|
tests_EntriesReport = tests "EntriesReport" [
|
||||||
tests "entriesReport" [
|
tests "entriesReport" [
|
||||||
test "not acct" $ (length $ entriesReport defreportopts (Not $ Acct "bank") samplejournal) `is` 1
|
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
|
,test "date" $ (length $ entriesReport defreportopts (Date $ mkdatespan "2008/06/01" "2008/07/01") samplejournal) `is` 3
|
||||||
|
|||||||
@ -16,7 +16,7 @@ module Hledger.Reports.MultiBalanceReports (
|
|||||||
tableAsText,
|
tableAsText,
|
||||||
|
|
||||||
-- -- * Tests
|
-- -- * Tests
|
||||||
easytests_MultiBalanceReports
|
tests_MultiBalanceReports
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -302,7 +302,7 @@ tableAsText (ReportOpts{pretty_tables_ = pretty}) showcell =
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_MultiBalanceReports = tests "MultiBalanceReports" [
|
tests_MultiBalanceReports = tests "MultiBalanceReports" [
|
||||||
let
|
let
|
||||||
(opts,journal) `gives` r = do
|
(opts,journal) `gives` r = do
|
||||||
let (eitems, etotal) = r
|
let (eitems, etotal) = r
|
||||||
|
|||||||
@ -12,7 +12,7 @@ module Hledger.Reports.PostingsReport (
|
|||||||
mkpostingsReportItem,
|
mkpostingsReportItem,
|
||||||
|
|
||||||
-- * Tests
|
-- * Tests
|
||||||
easytests_PostingsReport
|
tests_PostingsReport
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -217,7 +217,7 @@ summarisePostingsInDateSpan (DateSpan b e) wd depth showempty ps
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_PostingsReport = tests "PostingsReport" [
|
tests_PostingsReport = tests "PostingsReport" [
|
||||||
|
|
||||||
tests "postingsReport" $
|
tests "postingsReport" $
|
||||||
let (query, journal) `gives` n = (length $ snd $ postingsReport defreportopts query journal) `is` n
|
let (query, journal) `gives` n = (length $ snd $ postingsReport defreportopts query journal) `is` n
|
||||||
|
|||||||
@ -33,7 +33,7 @@ module Hledger.Reports.ReportOptions (
|
|||||||
specifiedStartDate,
|
specifiedStartDate,
|
||||||
specifiedEndDate,
|
specifiedEndDate,
|
||||||
|
|
||||||
easytests_ReportOptions
|
tests_ReportOptions
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -420,7 +420,7 @@ specifiedEndDate ropts = snd <$> specifiedStartEndDates ropts
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_ReportOptions = tests "ReportOptions" [
|
tests_ReportOptions = tests "ReportOptions" [
|
||||||
tests "queryFromOpts" [
|
tests "queryFromOpts" [
|
||||||
(queryFromOpts nulldate defreportopts) `is` Any
|
(queryFromOpts nulldate defreportopts) `is` Any
|
||||||
,(queryFromOpts nulldate defreportopts{query_="a"}) `is` (Acct "a")
|
,(queryFromOpts nulldate defreportopts{query_="a"}) `is` (Acct "a")
|
||||||
|
|||||||
@ -23,7 +23,7 @@ module Hledger.Reports.TransactionsReports (
|
|||||||
accountTransactionsReport,
|
accountTransactionsReport,
|
||||||
transactionsReportByCommodity,
|
transactionsReportByCommodity,
|
||||||
transactionRegisterDate,
|
transactionRegisterDate,
|
||||||
easytests_TransactionsReports
|
tests_TransactionsReports
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -278,5 +278,5 @@ filterTransactionsReportByCommodity c (label,items) =
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_TransactionsReports = tests "TransactionsReports" [
|
tests_TransactionsReports = tests "TransactionsReports" [
|
||||||
]
|
]
|
||||||
|
|||||||
@ -217,6 +217,6 @@ sequence' ms = do
|
|||||||
mapM' :: Monad f => (a -> f b) -> [a] -> f [b]
|
mapM' :: Monad f => (a -> f b) -> [a] -> f [b]
|
||||||
mapM' f = sequence' . map f
|
mapM' f = sequence' . map f
|
||||||
|
|
||||||
easytests_Utils = tests "Utils" [
|
tests_Utils = tests "Utils" [
|
||||||
easytests_Text
|
tests_Text
|
||||||
]
|
]
|
||||||
|
|||||||
@ -6,7 +6,7 @@
|
|||||||
module Hledger.Utils.Test (
|
module Hledger.Utils.Test (
|
||||||
HasCallStack
|
HasCallStack
|
||||||
,module EasyTest
|
,module EasyTest
|
||||||
,runEasyTests
|
,runEasytests
|
||||||
,tests
|
,tests
|
||||||
,_tests
|
,_tests
|
||||||
,test
|
,test
|
||||||
@ -70,20 +70,21 @@ tests name = E.scope name . E.tests
|
|||||||
_tests :: T.Text -> [E.Test ()] -> E.Test ()
|
_tests :: T.Text -> [E.Test ()] -> E.Test ()
|
||||||
_tests _name = (E.skip >>) . E.tests
|
_tests _name = (E.skip >>) . E.tests
|
||||||
|
|
||||||
-- | Run some easytests, returning True if there was a problem. Catches ExitCode.
|
-- | Run some easytest tests, catching easytest's ExitCode exception,
|
||||||
-- With arguments, runs only tests in the scope named by the first argument
|
-- returning True if there was a problem.
|
||||||
-- (case sensitive).
|
-- With arguments, runs only the scope (or single test) named by the first argument
|
||||||
|
-- (exact, case sensitive).
|
||||||
-- If there is a second argument, it should be an integer and will be used
|
-- If there is a second argument, it should be an integer and will be used
|
||||||
-- as the seed for randomness.
|
-- as the seed for randomness.
|
||||||
runEasyTests :: [String] -> E.Test () -> IO Bool
|
runEasytests :: [String] -> E.Test () -> IO Bool
|
||||||
runEasyTests args easytests = (do
|
runEasytests args tests = (do
|
||||||
case args of
|
case args of
|
||||||
[] -> E.run easytests
|
[] -> E.run tests
|
||||||
[a] -> E.runOnly (T.pack a) easytests
|
[a] -> E.runOnly (T.pack a) tests
|
||||||
a:b:_ -> do
|
a:b:_ -> do
|
||||||
case readMay b :: Maybe Int of
|
case readMay b :: Maybe Int of
|
||||||
Nothing -> error' "the second argument should be an integer (a seed for easytest)"
|
Nothing -> error' "the second argument should be an integer (a seed for easytest)"
|
||||||
Just seed -> E.rerunOnly seed (T.pack a) easytests
|
Just seed -> E.rerunOnly seed (T.pack a) tests
|
||||||
return False
|
return False
|
||||||
)
|
)
|
||||||
`catch` (\(_::ExitCode) -> return True)
|
`catch` (\(_::ExitCode) -> return True)
|
||||||
|
|||||||
@ -55,7 +55,7 @@ module Hledger.Utils.Text
|
|||||||
textPadLeftWide,
|
textPadLeftWide,
|
||||||
textPadRightWide,
|
textPadRightWide,
|
||||||
-- -- * tests
|
-- -- * tests
|
||||||
easytests_Text
|
tests_Text
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -420,7 +420,7 @@ textWidth s = maximum $ map (T.foldr (\a b -> charWidth a + b) 0) $ T.lines s
|
|||||||
-- | otherwise -> 1
|
-- | otherwise -> 1
|
||||||
|
|
||||||
|
|
||||||
easytests_Text = tests "Text" [
|
tests_Text = tests "Text" [
|
||||||
tests "quoteIfSpaced" [
|
tests "quoteIfSpaced" [
|
||||||
quoteIfSpaced "a'a" `is` "a'a"
|
quoteIfSpaced "a'a" `is` "a'a"
|
||||||
,quoteIfSpaced "a\"a" `is` "a\"a"
|
,quoteIfSpaced "a\"a" `is` "a\"a"
|
||||||
|
|||||||
@ -2,4 +2,4 @@
|
|||||||
Run hledger-lib's easytest tests using the easytest runner.
|
Run hledger-lib's easytest tests using the easytest runner.
|
||||||
-}
|
-}
|
||||||
import Hledger
|
import Hledger
|
||||||
main = run easytests_Hledger
|
main = run tests_Hledger
|
||||||
|
|||||||
@ -16,7 +16,7 @@ module Hledger.Cli (
|
|||||||
module Hledger.Cli.Utils,
|
module Hledger.Cli.Utils,
|
||||||
module Hledger.Cli.Version,
|
module Hledger.Cli.Version,
|
||||||
module Hledger,
|
module Hledger,
|
||||||
easytests_Cli,
|
tests_Cli,
|
||||||
module System.Console.CmdArgs.Explicit
|
module System.Console.CmdArgs.Explicit
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
@ -29,7 +29,7 @@ import Hledger.Cli.DocFiles
|
|||||||
import Hledger.Cli.Utils
|
import Hledger.Cli.Utils
|
||||||
import Hledger.Cli.Version
|
import Hledger.Cli.Version
|
||||||
|
|
||||||
easytests_Cli = tests "Cli" [
|
tests_Cli = tests "Cli" [
|
||||||
easytests_Hledger
|
tests_Hledger
|
||||||
,easytests_Commands
|
,tests_Commands
|
||||||
]
|
]
|
||||||
|
|||||||
@ -12,7 +12,7 @@ module Hledger.Cli.Commands (
|
|||||||
,builtinCommands
|
,builtinCommands
|
||||||
,builtinCommandNames
|
,builtinCommandNames
|
||||||
,printCommandsList
|
,printCommandsList
|
||||||
,easytests_Commands
|
,tests_Commands
|
||||||
,module Hledger.Cli.Commands.Accounts
|
,module Hledger.Cli.Commands.Accounts
|
||||||
,module Hledger.Cli.Commands.Activity
|
,module Hledger.Cli.Commands.Activity
|
||||||
,module Hledger.Cli.Commands.Add
|
,module Hledger.Cli.Commands.Add
|
||||||
@ -240,14 +240,14 @@ FLAGS
|
|||||||
testcmd :: CliOpts -> Journal -> IO ()
|
testcmd :: CliOpts -> Journal -> IO ()
|
||||||
testcmd opts _undefined = do
|
testcmd opts _undefined = do
|
||||||
let args = words' $ query_ $ reportopts_ opts
|
let args = words' $ query_ $ reportopts_ opts
|
||||||
e <- runEasyTests args $ EasyTest.tests [easytests_Hledger, easytests_Commands]
|
e <- runEasytests args $ EasyTest.tests [tests_Hledger, tests_Commands]
|
||||||
if e then exitFailure else exitSuccess
|
if e then exitFailure else exitSuccess
|
||||||
|
|
||||||
-- unit tests of hledger command-line executable
|
-- unit tests of hledger command-line executable
|
||||||
|
|
||||||
easytests_Commands = tests "Commands" [
|
tests_Commands = tests "Commands" [
|
||||||
easytests_Balance
|
tests_Balance
|
||||||
,easytests_Register
|
,tests_Register
|
||||||
|
|
||||||
-- some more tests easiest to define here:
|
-- some more tests easiest to define here:
|
||||||
|
|
||||||
|
|||||||
@ -247,7 +247,7 @@ module Hledger.Cli.Commands.Balance (
|
|||||||
,multiBalanceReportHtmlRows
|
,multiBalanceReportHtmlRows
|
||||||
,balanceReportAsTable
|
,balanceReportAsTable
|
||||||
,balanceReportTableAsText
|
,balanceReportTableAsText
|
||||||
,easytests_Balance
|
,tests_Balance
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
@ -630,7 +630,7 @@ balanceReportTableAsText ropts = tableAsText ropts showamt
|
|||||||
| otherwise = showMixedAmountOneLineWithoutPrice
|
| otherwise = showMixedAmountOneLineWithoutPrice
|
||||||
|
|
||||||
|
|
||||||
easytests_Balance = tests "Balance" [
|
tests_Balance = tests "Balance" [
|
||||||
|
|
||||||
tests "balanceReportAsText" [
|
tests "balanceReportAsText" [
|
||||||
test "unicode in balance layout" $ do
|
test "unicode in balance layout" $ do
|
||||||
|
|||||||
@ -12,7 +12,7 @@ module Hledger.Cli.Commands.Register (
|
|||||||
,postingsReportAsText
|
,postingsReportAsText
|
||||||
,postingsReportItemAsText
|
,postingsReportItemAsText
|
||||||
-- ,showPostingWithBalanceForVty
|
-- ,showPostingWithBalanceForVty
|
||||||
,easytests_Register
|
,tests_Register
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
@ -191,7 +191,7 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
|
|||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
easytests_Register = tests "Register" [
|
tests_Register = tests "Register" [
|
||||||
|
|
||||||
tests "postingsReportAsText" [
|
tests "postingsReportAsText" [
|
||||||
test "unicode in register layout" $ do
|
test "unicode in register layout" $ do
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user