diff --git a/hledger-lib/Hledger/Data.hs b/hledger-lib/Hledger/Data.hs index 18c73c514..baed3aad5 100644 --- a/hledger-lib/Hledger/Data.hs +++ b/hledger-lib/Hledger/Data.hs @@ -52,12 +52,9 @@ import Hledger.Utils.Test tests_Hledger_Data = TestList [ - tests_Hledger_Data_Account - ,tests_Hledger_Data_AccountName + tests_Hledger_Data_AccountName ,tests_Hledger_Data_Amount - ,tests_Hledger_Data_Commodity ,tests_Hledger_Data_Journal - ,tests_Hledger_Data_MarketPrice ,tests_Hledger_Data_Ledger ,tests_Hledger_Data_Posting -- ,tests_Hledger_Data_RawOptions diff --git a/hledger-lib/Hledger/Data/Account.hs b/hledger-lib/Hledger/Data/Account.hs index 1280bd8fb..917f3bc45 100644 --- a/hledger-lib/Hledger/Data/Account.hs +++ b/hledger-lib/Hledger/Data/Account.hs @@ -236,8 +236,3 @@ showAccountDebug a = printf "%-25s %4s %4s %s" (showMixedAmount $ aebalance a) (showMixedAmount $ aibalance a) (if aboring a then "b" else " " :: String) - - -tests_Hledger_Data_Account = TestList [ - ] - diff --git a/hledger-lib/Hledger/Data/Commodity.hs b/hledger-lib/Hledger/Data/Commodity.hs index 710607ec8..4e095c708 100644 --- a/hledger-lib/Hledger/Data/Commodity.hs +++ b/hledger-lib/Hledger/Data/Commodity.hs @@ -79,6 +79,3 @@ conversionRate _ _ = 1 -- commoditieswithsymbol s = filter ((s==) . symbol) cs -- symbols = nub $ map symbol cs -tests_Hledger_Data_Commodity = TestList [ - ] - diff --git a/hledger-lib/Hledger/Data/MarketPrice.hs b/hledger-lib/Hledger/Data/MarketPrice.hs index c500fdb0e..a06a1612e 100644 --- a/hledger-lib/Hledger/Data/MarketPrice.hs +++ b/hledger-lib/Hledger/Data/MarketPrice.hs @@ -17,7 +17,6 @@ import qualified Data.Text as T import Hledger.Data.Amount import Hledger.Data.Dates import Hledger.Data.Types -import Hledger.Utils.Test -- | Get the string representation of an market price, based on its -- commodity's display settings. @@ -28,5 +27,3 @@ showMarketPrice mp = unwords , T.unpack (mpcommodity mp) , (showAmount . setAmountPrecision maxprecision) (mpamount mp) ] - -tests_Hledger_Data_MarketPrice = TestList [] diff --git a/hledger-lib/Hledger/Read.hs b/hledger-lib/Hledger/Read.hs index 0f7fb47f6..3a28750f6 100644 --- a/hledger-lib/Hledger/Read.hs +++ b/hledger-lib/Hledger/Read.hs @@ -345,9 +345,6 @@ samplejournal = readJournal' $ T.unlines tests_Hledger_Read = TestList $ tests_readJournal' ++ [ --- LedgerReader.tests_Hledger_Read_LedgerReader, - TimeclockReader.tests_Hledger_Read_TimeclockReader, - TimedotReader.tests_Hledger_Read_TimedotReader, CsvReader.tests_Hledger_Read_CsvReader, "journal" ~: do diff --git a/hledger-lib/Hledger/Read/TimeclockReader.hs b/hledger-lib/Hledger/Read/TimeclockReader.hs index ac5ed7356..22bc2901c 100644 --- a/hledger-lib/Hledger/Read/TimeclockReader.hs +++ b/hledger-lib/Hledger/Read/TimeclockReader.hs @@ -47,8 +47,6 @@ module Hledger.Read.TimeclockReader ( reader, -- * Misc other exports timeclockfilep, - -- * Tests - tests_Hledger_Read_TimeclockReader ) where import Prelude () @@ -115,6 +113,4 @@ timeclockentryp = do description <- T.pack . fromMaybe "" <$> lift (optional (skipSome spacenonewline >> restofline)) return $ TimeclockEntry sourcepos (read [code]) datetime account description -tests_Hledger_Read_TimeclockReader = TestList [ - ] diff --git a/hledger-lib/Hledger/Read/TimedotReader.hs b/hledger-lib/Hledger/Read/TimedotReader.hs index 11f933b24..77fb37b7a 100644 --- a/hledger-lib/Hledger/Read/TimedotReader.hs +++ b/hledger-lib/Hledger/Read/TimedotReader.hs @@ -30,8 +30,6 @@ module Hledger.Read.TimedotReader ( reader, -- * Misc other exports timedotfilep, - -- * Tests - tests_Hledger_Read_TimedotReader ) where import Prelude () @@ -172,7 +170,3 @@ timedotdotsp :: JournalParser m Quantity timedotdotsp = do dots <- filter (not.isSpace) <$> many (oneOf (". " :: [Char])) return $ (/4) $ fromIntegral $ length dots - -tests_Hledger_Read_TimedotReader = TestList [ - ] - diff --git a/hledger-lib/Hledger/Reports.hs b/hledger-lib/Hledger/Reports.hs index 155719af2..d2faa1195 100644 --- a/hledger-lib/Hledger/Reports.hs +++ b/hledger-lib/Hledger/Reports.hs @@ -42,6 +42,5 @@ tests_Hledger_Reports = TestList $ tests_Hledger_Reports_EntriesReport, tests_Hledger_Reports_PostingsReport, tests_Hledger_Reports_BalanceReport, - tests_Hledger_Reports_MultiBalanceReport, - tests_Hledger_Reports_BudgetReport + tests_Hledger_Reports_MultiBalanceReport ] diff --git a/hledger-lib/Hledger/Reports/BalanceHistoryReport.hs b/hledger-lib/Hledger/Reports/BalanceHistoryReport.hs index 2bfbe3b21..8f3937fb4 100644 --- a/hledger-lib/Hledger/Reports/BalanceHistoryReport.hs +++ b/hledger-lib/Hledger/Reports/BalanceHistoryReport.hs @@ -8,9 +8,6 @@ Account balance history report. module Hledger.Reports.BalanceHistoryReport ( accountBalanceHistory - - -- -- * Tests - -- tests_Hledger_Reports_BalanceReport ) where diff --git a/hledger-lib/Hledger/Reports/BudgetReport.hs b/hledger-lib/Hledger/Reports/BudgetReport.hs index 6eb2180ae..dffcd293f 100644 --- a/hledger-lib/Hledger/Reports/BudgetReport.hs +++ b/hledger-lib/Hledger/Reports/BudgetReport.hs @@ -353,6 +353,3 @@ budgetReportAsTable maybeAccountNameDrop :: ReportOpts -> AccountName -> AccountName maybeAccountNameDrop opts a | flat_ opts = accountNameDrop (drop_ opts) a | otherwise = a - -tests_Hledger_Reports_BudgetReport = TestList [ - ] diff --git a/hledger-lib/Hledger/Reports/TransactionsReports.hs b/hledger-lib/Hledger/Reports/TransactionsReports.hs index bf08fa905..f1cf14bdf 100644 --- a/hledger-lib/Hledger/Reports/TransactionsReports.hs +++ b/hledger-lib/Hledger/Reports/TransactionsReports.hs @@ -23,9 +23,6 @@ module Hledger.Reports.TransactionsReports ( accountTransactionsReport, transactionsReportByCommodity, transactionRegisterDate - - -- -- * Tests - -- tests_Hledger_Reports_TransactionsReports ) where diff --git a/hledger-lib/Hledger/Utils/Test.hs b/hledger-lib/Hledger/Utils/Test.hs index b1bb34c0a..15c8de38b 100644 --- a/hledger-lib/Hledger/Utils/Test.hs +++ b/hledger-lib/Hledger/Utils/Test.hs @@ -185,14 +185,6 @@ assertParseEqual' parse expected = (\actual -> assertEqual (unlines ["expected: " ++ show expected, " but got: " ++ show actual]) expected actual) $ runIdentity parse ----- | Labelled version of assertParseEqual'. ---assertParseEqual'' :: (Show a, Eq a, Show t, Show e) => String -> Identity (Either (ParseError t e) a) -> a -> Assertion ---assertParseEqual'' label parse expected = --- either --- (assertFailure . ("parse error: "++) . pshow) --- (\actual -> assertEqual (unlines [label, "expected: " ++ show expected, " but got: " ++ show actual]) expected actual) --- $ runIdentity parse - -- | Run some hunit tests, returning True if there was a problem. -- With arguments, runs only tests whose names contain the first argument -- (case sensitive). @@ -210,58 +202,3 @@ runHunitTests args hunittests = do runTestTTStdout t = do (counts, 0) <- U.runTestText (putTextToHandle stdout True) t return counts - --- matchedTests opts ts --- | tree_ $ reportopts_ opts = --- -- Tests, filtered by any arguments, in a flat list with simple names. --- TestList $ --- filter (matchesAccount (queryFromOpts nulldate $ reportopts_ opts) . T.pack . testName) $ --- flattenTests ts --- | otherwise = --- -- Tests, filtered by any arguments, in the original suites with hierarchical names. --- filterTests (matchesAccount (queryFromOpts nulldate $ reportopts_ opts) . T.pack . testName) --- ts - --- -- | Like runTestTT but can optionally not erase progress output. --- runTestTT' verbose t = do --- (counts, 0) <- runTestText' (f stderr True) t --- return counts --- where f | verbose = putTextToHandle' --- | otherwise = putTextToHandle - --- -- | Like runTestText but also prints test names if any. --- runTestText' :: PutText st -> Test -> IO (Counts, st) --- runTestText' _pt _t@(TestLabel _label _) = error "HERE" -- hPutStrLn stderr label >> runTestText pt t --- runTestText' pt t = runTestText pt t - --- -- runTestText' (PutText put us0) t = do --- -- (counts', us1) <- trace "XXX" $ performTest reportStart reportError reportFailure us0 t --- -- us2 <- put (showCounts counts' ++ " :::: " ++ testName t) True us1 --- -- return (counts', us2) --- -- where --- -- reportStart ss us = put (showCounts (counts ss)) False us --- -- reportError = reportProblem "Error:" "Error in: " --- -- reportFailure = reportProblem "Failure:" "Failure in: " --- -- reportProblem p0 p1 loc msg ss us = put line True us --- -- where line = "### " ++ kind ++ path' ++ "\n" ++ formatLocation loc ++ msg --- -- kind = if null path' then p0 else p1 --- -- path' = showPath (path ss) - --- -- formatLocation :: Maybe SrcLoc -> String --- -- formatLocation Nothing = "" --- -- formatLocation (Just loc) = srcLocFile loc ++ ":" ++ show (srcLocStartLine loc) ++ "\n" - --- -- | Like putTextToHandle but does not erase progress lines. --- putTextToHandle' --- :: Handle --- -> Bool -- ^ Write progress lines to handle? --- -> PutText Int --- putTextToHandle' handle showProgress = PutText put initCnt --- where --- initCnt = if showProgress then 0 else -1 --- put line pers (-1) = do when pers (hPutStrLn handle line); return (-1) --- put line True cnt = do hPutStrLn handle (erase cnt ++ line); return 0 --- put line False _ = do hPutStr handle ('\n' : line); return (length line) --- -- The "erasing" strategy with a single '\r' relies on the fact that the --- -- lengths of successive summary lines are monotonically nondecreasing. --- erase cnt = if cnt == 0 then "" else "\r" ++ replicate cnt ' ' ++ "\r" diff --git a/hledger-ui/Hledger/UI.hs b/hledger-ui/Hledger/UI.hs index a5afe11d2..2323aca50 100644 --- a/hledger-ui/Hledger/UI.hs +++ b/hledger-ui/Hledger/UI.hs @@ -14,10 +14,3 @@ import Hledger.UI.Main import Hledger.UI.UIOptions import Hledger.UI.Theme import Test.HUnit as U - -tests_Hledger_UI :: U.Test -tests_Hledger_UI = TestList - [ - -- tests_Hledger_UI_Main - -- tests_Hledger_UI_UIOptions - ] diff --git a/hledger-web/Hledger/Web.hs b/hledger-web/Hledger/Web.hs index 19b90df03..38d0b73e3 100644 --- a/hledger-web/Hledger/Web.hs +++ b/hledger-web/Hledger/Web.hs @@ -11,10 +11,3 @@ module Hledger.Web import Hledger.Web.WebOptions import Hledger.Web.Main import Test.HUnit as U - -tests_Hledger_Web :: U.Test -tests_Hledger_Web = TestList - [ - -- tests_Hledger_Web_WebOptions - -- ,tests_Hledger_Web_Main - ] diff --git a/hledger/Hledger/Cli/CliOptions.hs b/hledger/Hledger/Cli/CliOptions.hs index bc25e38ed..28f812e86 100644 --- a/hledger/Hledger/Cli/CliOptions.hs +++ b/hledger/Hledger/Cli/CliOptions.hs @@ -60,9 +60,6 @@ module Hledger.Cli.CliOptions ( hledgerAddons, topicForMode, - -- * Tests - tests_Hledger_Cli_CliOptions, - -- -- * Convenience re-exports -- module Data.String.Here, -- module System.Console.CmdArgs.Explicit, @@ -705,8 +702,3 @@ getDirectoryContentsSafe d = -- d <- getCurrentDay -- putStrLn $ "search query: " ++ (show $ queryFromOpts d $ reportopts_ opts) --- tests - -tests_Hledger_Cli_CliOptions = TestList - [ - ] diff --git a/hledger/Hledger/Cli/Commands.hs b/hledger/Hledger/Cli/Commands.hs index 2c384dcb1..ca4257eb2 100644 --- a/hledger/Hledger/Cli/Commands.hs +++ b/hledger/Hledger/Cli/Commands.hs @@ -257,16 +257,8 @@ testcmd opts _undefined = do tests_Hledger_Cli_Commands = TestList [ tests_Hledger - ,tests_Hledger_Cli_CliOptions - -- ,tests_Hledger_Cli_Commands_Activity - -- ,tests_Hledger_Cli_Commands_Add ,tests_Hledger_Cli_Commands_Balance - ,tests_Hledger_Cli_Commands_Balancesheet - ,tests_Hledger_Cli_Commands_Cashflow - ,tests_Hledger_Cli_Commands_Incomestatement - ,tests_Hledger_Cli_Commands_Print ,tests_Hledger_Cli_Commands_Register - -- ,tests_Hledger_Cli_Commands_Stats -- some more tests easiest to define here: diff --git a/hledger/Hledger/Cli/Commands/Accounts.hs b/hledger/Hledger/Cli/Commands/Accounts.hs index 5e55e14c2..96ed4483d 100644 --- a/hledger/Hledger/Cli/Commands/Accounts.hs +++ b/hledger/Hledger/Cli/Commands/Accounts.hs @@ -16,7 +16,6 @@ The @accounts@ command lists account names: module Hledger.Cli.Commands.Accounts ( accountsmode ,accounts - ,tests_Hledger_Cli_Commands_Accounts ) where import Data.List @@ -80,5 +79,3 @@ accounts CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do render a | tree_ ropts = T.replicate (2 * (accountNameLevel a - 1)) " " <> accountLeafName a | otherwise = maybeAccountNameDrop ropts a mapM_ (putStrLn . T.unpack . render) as' - -tests_Hledger_Cli_Commands_Accounts = TestList [] diff --git a/hledger/Hledger/Cli/Commands/Balancesheet.hs b/hledger/Hledger/Cli/Commands/Balancesheet.hs index 239a5a9f7..252ec5eec 100644 --- a/hledger/Hledger/Cli/Commands/Balancesheet.hs +++ b/hledger/Hledger/Cli/Commands/Balancesheet.hs @@ -8,7 +8,6 @@ The @balancesheet@ command prints a simple balance sheet. module Hledger.Cli.Commands.Balancesheet ( balancesheetmode ,balancesheet - ,tests_Hledger_Cli_Commands_Balancesheet ) where import Data.String.Here @@ -55,6 +54,3 @@ balancesheetmode = compoundBalanceCommandMode balancesheetSpec balancesheet :: CliOpts -> Journal -> IO () balancesheet = compoundBalanceCommand balancesheetSpec -tests_Hledger_Cli_Commands_Balancesheet = TestList - [ - ] diff --git a/hledger/Hledger/Cli/Commands/Cashflow.hs b/hledger/Hledger/Cli/Commands/Cashflow.hs index 763a1c1b0..b3d590661 100644 --- a/hledger/Hledger/Cli/Commands/Cashflow.hs +++ b/hledger/Hledger/Cli/Commands/Cashflow.hs @@ -11,7 +11,6 @@ cash flows.) module Hledger.Cli.Commands.Cashflow ( cashflowmode ,cashflow - ,tests_Hledger_Cli_Commands_Cashflow ) where import Data.String.Here @@ -51,7 +50,3 @@ cashflowmode = compoundBalanceCommandMode cashflowSpec cashflow :: CliOpts -> Journal -> IO () cashflow = compoundBalanceCommand cashflowSpec - -tests_Hledger_Cli_Commands_Cashflow = TestList - [ - ] diff --git a/hledger/Hledger/Cli/Commands/Checkdates.hs b/hledger/Hledger/Cli/Commands/Checkdates.hs index 9b0df88e8..903fab5ab 100755 --- a/hledger/Hledger/Cli/Commands/Checkdates.hs +++ b/hledger/Hledger/Cli/Commands/Checkdates.hs @@ -4,7 +4,6 @@ module Hledger.Cli.Commands.Checkdates ( checkdatesmode ,checkdates - ,tests_Hledger_Cli_Commands_Checkdates ) where import Data.String.Here @@ -78,7 +77,3 @@ checkTransactions compare ts = if compare previous current then acc{fa_previous=Just current} else acc{fa_error=Just current} - -tests_Hledger_Cli_Commands_Checkdates = TestList - [ - ] diff --git a/hledger/Hledger/Cli/Commands/Incomestatement.hs b/hledger/Hledger/Cli/Commands/Incomestatement.hs index edd5ce123..e93081809 100644 --- a/hledger/Hledger/Cli/Commands/Incomestatement.hs +++ b/hledger/Hledger/Cli/Commands/Incomestatement.hs @@ -8,7 +8,6 @@ The @incomestatement@ command prints a simple income statement (profit & loss re module Hledger.Cli.Commands.Incomestatement ( incomestatementmode ,incomestatement - ,tests_Hledger_Cli_Commands_Incomestatement ) where import Data.String.Here @@ -54,7 +53,3 @@ incomestatementmode = compoundBalanceCommandMode incomestatementSpec incomestatement :: CliOpts -> Journal -> IO () incomestatement = compoundBalanceCommand incomestatementSpec - -tests_Hledger_Cli_Commands_Incomestatement = TestList - [ - ] diff --git a/hledger/Hledger/Cli/Commands/Print.hs b/hledger/Hledger/Cli/Commands/Print.hs index 29bd8a3ee..58a17ed14 100644 --- a/hledger/Hledger/Cli/Commands/Print.hs +++ b/hledger/Hledger/Cli/Commands/Print.hs @@ -11,7 +11,6 @@ module Hledger.Cli.Commands.Print ( ,print' -- ,entriesReportAsText ,originalTransaction - ,tests_Hledger_Cli_Commands_Print ) where @@ -180,8 +179,3 @@ printMatch CliOpts{reportopts_=ropts} j desc = do | otherwise = Just $ snd $ head historymatches where historymatches = transactionsSimilarTo j q desc - --- tests - -tests_Hledger_Cli_Commands_Print = TestList [] - -- tests_showTransactions