tests: export HUnit/EasyTest from Hledger.Utils.Test; more helpers

This commit is contained in:
Simon Michael 2018-08-18 07:33:41 +01:00
parent 4d578c008f
commit d778a92561
47 changed files with 131 additions and 170 deletions

View File

@ -6,8 +6,6 @@ module Hledger (
,Hledger.easytests
)
where
import Test.HUnit hiding (test)
import EasyTest
import Hledger.Data as X hiding (easytests)
import qualified Hledger.Data (easytests)
@ -26,7 +24,7 @@ tests_Hledger = TestList
,tests_Hledger_Utils
]
easytests = test "Hledger" $ tests [
easytests = tests "Hledger" [
Hledger.Data.easytests
,Hledger.Read.easytests
]

View File

@ -28,7 +28,6 @@ module Hledger.Data (
tests_Hledger_Data
)
where
import Test.HUnit
import Hledger.Data.Account
import Hledger.Data.AccountName
@ -47,8 +46,8 @@ import Hledger.Data.Timeclock
import Hledger.Data.Transaction
import Hledger.Data.TransactionModifier
import Hledger.Data.Types
import Hledger.Utils.Test
tests_Hledger_Data :: Test
tests_Hledger_Data = TestList
[
tests_Hledger_Data_Account

View File

@ -16,7 +16,6 @@ import Data.Ord
import qualified Data.Map as M
import Data.Text (pack,unpack)
import Safe (headMay, lookupJustDef)
import Test.HUnit
import Text.Printf
import Hledger.Data.AccountName

View File

@ -18,7 +18,6 @@ import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import Data.Tree
import Test.HUnit
import Text.Printf
import Hledger.Data.Types

View File

@ -128,7 +128,6 @@ import Data.Ord (comparing)
-- import Data.Text (Text)
import qualified Data.Text as T
import Safe (maximumDef)
import Test.HUnit
import Text.Printf
import qualified Data.Map as M

View File

@ -19,7 +19,6 @@ import Data.Maybe (fromMaybe)
import Data.Monoid
#endif
import qualified Data.Text as T
import Test.HUnit
-- import qualified Data.Map as M
import Hledger.Data.Types

View File

@ -92,12 +92,10 @@ import Data.Ord
import qualified Data.Semigroup as Sem
import Data.Text (Text)
import qualified Data.Text as T
import EasyTest
import Safe (headMay, headDef)
import Data.Time.Calendar
import Data.Tree
import System.Time (ClockTime(TOD))
import Test.HUnit hiding (test)
import Text.Printf
import qualified Data.Map as M
@ -1088,18 +1086,18 @@ tests_Hledger_Data_Journal = TestList $
-- journalProfitAndLossAccountNames j `is` ["expenses","expenses:e","income","income:i"]
]
easytests = test "Journal" $ tests [
easytests = tests "Journal" [
test "standard account types" $ do
let
j = samplejournal
journalAccountNamesMatching :: Query -> Journal -> [AccountName]
journalAccountNamesMatching q = filter (q `matchesAccount`) . journalAccountNames
namesfrom qfunc = journalAccountNamesMatching (qfunc j) j
tests
[ "assets" $ expectEq (namesfrom journalAssetAccountQuery) ["assets","assets:bank","assets:bank:checking","assets:bank:saving","assets:cash"]
, "liabilities" $ expectEq (namesfrom journalLiabilityAccountQuery) ["liabilities","liabilities:debts"]
, "equity" $ expectEq (namesfrom journalEquityAccountQuery) []
, "income" $ expectEq (namesfrom journalIncomeAccountQuery) ["income","income:gifts","income:salary"]
, "expenses" $ expectEq (namesfrom journalExpenseAccountQuery) ["expenses","expenses:food","expenses:supplies"]
tests ""
[ test "assets" $ expectEq (namesfrom journalAssetAccountQuery) ["assets","assets:bank","assets:bank:checking","assets:bank:saving","assets:cash"]
, test "liabilities" $ expectEq (namesfrom journalLiabilityAccountQuery) ["liabilities","liabilities:debts"]
, test "equity" $ expectEq (namesfrom journalEquityAccountQuery) []
, test "income" $ expectEq (namesfrom journalIncomeAccountQuery) ["income","income:gifts","income:salary"]
, test "expenses" $ expectEq (namesfrom journalExpenseAccountQuery) ["expenses","expenses:food","expenses:supplies"]
]
]

View File

@ -13,9 +13,9 @@ import qualified Data.Map as M
-- import Data.Text (Text)
import qualified Data.Text as T
import Safe (headDef)
import Test.HUnit
import Text.Printf
import Hledger.Utils.Test
import Hledger.Data.Types
import Hledger.Data.Account
import Hledger.Data.Journal

View File

@ -13,11 +13,11 @@ value of things at a given date.
module Hledger.Data.MarketPrice
where
import qualified Data.Text as T
import Test.HUnit
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.

View File

@ -68,7 +68,6 @@ import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Safe
import Test.HUnit
import Hledger.Utils
import Hledger.Data.Types

View File

@ -18,12 +18,13 @@ import "base-compat-batteries" Prelude.Compat
import Numeric
import Data.Char (isPrint)
import Data.Maybe
import Test.HUnit
import qualified Test.HUnit as U (test)
import Text.Megaparsec
import Text.Megaparsec.Char
import Hledger.Utils.Parse
import Hledger.Utils.String (formatString)
import Hledger.Utils.Test
-- | A format specification/template to use when rendering a report line item as text.
--
@ -148,7 +149,7 @@ testParser s expected = case (parseStringFormat s) of
Left error -> assertFailure $ show error
Right actual -> assertEqual ("Input: " ++ s) expected actual
tests_Hledger_Data_StringFormat = test [ formattingTests ++ parserTests ]
tests_Hledger_Data_StringFormat = U.test [ formattingTests ++ parserTests ]
formattingTests = [
testFormat (FormatLiteral " ") "" " "

View File

@ -20,7 +20,6 @@ import Data.Time.LocalTime
#if !(MIN_VERSION_time(1,5,0))
import System.Locale (defaultTimeLocale)
#endif
import Test.HUnit
import Text.Printf
import Hledger.Utils

View File

@ -53,7 +53,6 @@ import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Test.HUnit
import Text.Printf
import qualified Data.Map as Map

View File

@ -60,7 +60,6 @@ import Data.Monoid ((<>))
import qualified Data.Text as T
import Data.Time.Calendar
import Safe (readDef, headDef)
import Test.HUnit
import Text.Megaparsec
import Text.Megaparsec.Char
@ -796,7 +795,6 @@ matchesMarketPrice _ _ = True
-- tests
tests_Hledger_Query :: Test
tests_Hledger_Query = TestList $
tests_simplifyQuery
++ tests_words''

View File

@ -45,14 +45,12 @@ import Data.Ord
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time (Day)
import EasyTest
import Safe
import System.Directory (doesFileExist, getHomeDirectory)
import System.Environment (getEnv)
import System.Exit (exitFailure)
import System.FilePath
import System.IO
import Test.HUnit hiding (test)
import Text.Printf
import Hledger.Data.Dates (getCurrentDay, parsedate, showDate)
@ -364,7 +362,7 @@ tests_Hledger_Read = TestList $
]
easytests = test "Read" $ tests [
easytests = tests "Read" [
Hledger.Read.Common.easytests
,JournalReader.easytests
]

View File

@ -118,8 +118,6 @@ import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.LocalTime
import System.Time (getClockTime)
import Test.HUnit hiding (test)
import EasyTest hiding (char, char')
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Char.Lexer (decimal)
@ -1234,8 +1232,8 @@ tests_Hledger_Read_Common = TestList [
test_spaceandamountormissingp
]
easytests = test "Common" $ tests [
test "amountp" $ tests [
easytests = tests "Common" [
tests "amountp" [
test "basic" $ expectParseEq amountp "$47.18" (usd 47.18)
,test "ends-with-decimal-mark" $ expectParseEq amountp "$1." (usd 1 `withPrecision` 0)
,test "unit-price" $ expectParseEq amountp "$10 @ €0.5"

View File

@ -34,7 +34,6 @@ import Control.Exception hiding (try)
import Control.Monad
import Control.Monad.Except
import Control.Monad.State.Strict (StateT, get, modify', evalStateT)
-- import Test.HUnit
import Data.Char (toLower, isDigit, isSpace)
import "base-compat-batteries" Data.List.Compat
import Data.List.NonEmpty (fromList)
@ -54,7 +53,6 @@ import System.Locale (defaultTimeLocale)
import Safe
import System.Directory (doesFileExist)
import System.FilePath
import Test.HUnit hiding (State)
import Text.CSV (parseCSV, CSV)
import Text.Megaparsec hiding (parse)
import Text.Megaparsec.Char

View File

@ -84,9 +84,7 @@ import Data.List
import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.LocalTime
import EasyTest hiding (char, char')
import Safe
import Test.HUnit hiding (test)
import Text.Megaparsec hiding (parse)
import Text.Megaparsec.Char
import Text.Megaparsec.Custom
@ -816,8 +814,8 @@ tests_Hledger_Read_JournalReader = TestList $ concat [
]]
-}
easytests = test "JournalReader" $ tests [
test "periodictransactionp" $ tests [
easytests = tests "JournalReader" [
tests "periodictransactionp" [
test "more-period-text-in-comment" $ expectParseEqIO periodictransactionp
"~ monthly from 2018/6 ;In 2019 we will change this\n"
nullperiodictransaction {

View File

@ -59,7 +59,6 @@ import Control.Monad.State.Strict
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Test.HUnit
import Text.Megaparsec hiding (parse)
import Text.Megaparsec.Char

View File

@ -43,7 +43,6 @@ import Data.Char (isSpace)
import Data.List (foldl')
import Data.Maybe
import Data.Text (Text)
import Test.HUnit
import Text.Megaparsec hiding (parse)
import Text.Megaparsec.Char

View File

@ -24,8 +24,6 @@ module Hledger.Reports (
)
where
import Test.HUnit
import Hledger.Reports.ReportOptions
import Hledger.Reports.ReportTypes
import Hledger.Reports.EntriesReport
@ -35,8 +33,8 @@ import Hledger.Reports.BalanceReport
import Hledger.Reports.MultiBalanceReports
import Hledger.Reports.BudgetReport
-- import Hledger.Reports.BalanceHistoryReport
import Hledger.Utils.Test
tests_Hledger_Reports :: Test
tests_Hledger_Reports = TestList $
-- ++ tests_isInterestingIndented
[

View File

@ -15,7 +15,6 @@ module Hledger.Reports.BalanceHistoryReport (
where
import Data.Time.Calendar
-- import Test.HUnit
import Hledger.Data
import Hledger.Query

View File

@ -28,7 +28,6 @@ import Data.List
import Data.Ord
import Data.Maybe
import Data.Time.Calendar
import Test.HUnit
import Hledger.Data
import Hledger.Read (mamountp')
@ -397,6 +396,5 @@ Right samplejournal2 =
-- (defreportopts, samplejournal, "expenses") `gives` True
-- ]
tests_Hledger_Reports_BalanceReport :: Test
tests_Hledger_Reports_BalanceReport = TestList
tests_balanceReport

View File

@ -17,7 +17,6 @@ import Data.Monoid ((<>))
import Data.Ord
import Data.Time.Calendar
import Safe
import Test.HUnit
--import Data.List
--import Data.Maybe
import qualified Data.Map as Map
@ -27,7 +26,6 @@ import qualified Data.Text as T
--import System.Console.CmdArgs.Explicit as C
--import Lucid as L
--import Text.CSV
--import Test.HUnit
import Text.Printf (printf)
import Text.Tabular as T
--import Text.Tabular.AsciiWide
@ -356,6 +354,5 @@ maybeAccountNameDrop :: ReportOpts -> AccountName -> AccountName
maybeAccountNameDrop opts a | flat_ opts = accountNameDrop (drop_ opts) a
| otherwise = a
tests_Hledger_Reports_BudgetReport :: Test
tests_Hledger_Reports_BudgetReport = TestList [
]

View File

@ -16,11 +16,11 @@ where
import Data.List
import Data.Ord
import Test.HUnit
import Hledger.Data
import Hledger.Query
import Hledger.Reports.ReportOptions
import Hledger.Utils
-- | A journal entries report is a list of whole transactions as
@ -37,7 +37,6 @@ entriesReport opts q j =
date = transactionDateFn opts
ts = jtxns $ journalSelectingAmountFromOpts opts j
tests_entriesReport :: [Test]
tests_entriesReport = [
"entriesReport" ~: do
assertEqual "not acct" 1 (length $ entriesReport defreportopts (Not $ Acct "bank") samplejournal)
@ -45,7 +44,6 @@ tests_entriesReport = [
assertEqual "date" 3 (length $ entriesReport defreportopts (Date sp) samplejournal)
]
tests_Hledger_Reports_EntriesReport :: Test
tests_Hledger_Reports_EntriesReport = TestList $
tests_entriesReport

View File

@ -25,7 +25,6 @@ import Data.Maybe
import Data.Ord
import Data.Time.Calendar
import Safe
import Test.HUnit
import Text.Tabular as T
import Text.Tabular.AsciiWide
@ -348,6 +347,5 @@ tableAsText (ReportOpts{pretty_tables_ = pretty}) showcell =
acctswidth = maximum' $ map strWidth (headerContents l)
l' = padRightWide acctswidth <$> l
tests_Hledger_Reports_MultiBalanceReport :: Test
tests_Hledger_Reports_MultiBalanceReport = TestList
tests_multiBalanceReport

View File

@ -23,7 +23,6 @@ import Data.Ord (comparing)
import qualified Data.Text as T
import Data.Time.Calendar
import Safe (headMay, lastMay)
import Test.HUnit
import Hledger.Data
import Hledger.Query
@ -423,7 +422,6 @@ tests_postingsReport = [
-}
]
tests_Hledger_Reports_PostingsReport :: Test
tests_Hledger_Reports_PostingsReport = TestList $
tests_summarisePostingsByInterval
++ tests_postingsReport

View File

@ -47,7 +47,6 @@ import Data.Default
import Safe
import System.Console.ANSI (hSupportsANSI)
import System.IO (stdout)
import Test.HUnit
import Text.Megaparsec.Error
import Hledger.Data
@ -372,7 +371,6 @@ queryFromOptsOnly _d ReportOpts{..} = simplifyQuery flagsq
++ [Or $ map StatusQ statuses_]
++ (maybe [] ((:[]) . Depth) depth_)
tests_queryFromOpts :: [Test]
tests_queryFromOpts = [
"queryFromOpts" ~: do
assertEqual "" Any (queryFromOpts nulldate defreportopts)
@ -395,7 +393,6 @@ queryOptsFromOpts d ReportOpts{..} = flagsqopts ++ argsqopts
flagsqopts = []
argsqopts = snd $ parseQuery d (T.pack query_)
tests_queryOptsFromOpts :: [Test]
tests_queryOptsFromOpts = [
"queryOptsFromOpts" ~: do
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts)
@ -445,7 +442,6 @@ specifiedEndDate :: ReportOpts -> IO (Maybe Day)
specifiedEndDate ropts = snd <$> specifiedStartEndDates ropts
tests_Hledger_Reports_ReportOptions :: Test
tests_Hledger_Reports_ReportOptions = TestList $
tests_queryFromOpts
++ tests_queryOptsFromOpts

View File

@ -34,7 +34,6 @@ import Data.Ord
-- import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
-- import Test.HUnit
import Hledger.Data
import Hledger.Query

View File

@ -14,7 +14,6 @@ module Hledger.Utils (---- provide these frequently used modules - or not, for c
-- module Data.Time.LocalTime,
-- module Data.Tree,
-- module Text.RegexPR,
-- module Test.HUnit,
-- module Text.Printf,
---- all of this one:
module Hledger.Utils,
@ -33,7 +32,6 @@ module Hledger.Utils (---- provide these frequently used modules - or not, for c
-- the rest need to be done in each module I think
)
where
import Test.HUnit
import Control.Monad (liftM, when)
-- import Data.Char
@ -218,7 +216,6 @@ sequence' ms = do
mapM' :: Monad f => (a -> f b) -> [a] -> f [b]
mapM' f = sequence' . map f
tests_Hledger_Utils :: Test
tests_Hledger_Utils = TestList [
tests_Hledger_Utils_Text
]

View File

@ -1,7 +1,28 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hledger.Utils.Test where
module Hledger.Utils.Test (
-- * easytest
module E
,runEasyTests
,Hledger.Utils.Test.tests
,_tests
,test
,_test
,it
,_it
,expectParseEq
,expectParseEqIO
-- * HUnit
,module U
,runHunitTests
,assertParse
,assertParseFailure
,assertParseEqual
,assertParseEqual'
,is
) where
import Control.Exception
import Control.Monad
@ -10,33 +31,101 @@ import Data.CallStack
import Data.Functor.Identity
import Data.List
import qualified Data.Text as T
import EasyTest
import Safe
import System.Exit
import System.IO
import Test.HUnit as HUnit hiding (test)
import Text.Megaparsec
import Text.Megaparsec.Custom
import EasyTest as E hiding (char, char', tests)
import EasyTest (tests)
import Test.HUnit as U hiding (Test, test)
import qualified Test.HUnit as U (Test)
import Hledger.Utils.Debug (pshow)
import Hledger.Utils.Parse (parseWithState)
import Hledger.Utils.UTF8IOCompat (error')
-- * easytest helpers
-- | Name the given test(s). A readability synonym for easytest's "scope".
test :: T.Text -> E.Test a -> E.Test a
test = E.scope
-- | Skip the given test(s), with the same type signature as "test".
_test :: T.Text -> E.Test a -> E.Test a
_test _name = (E.skip >>)
-- | Name the given test(s). A synonym for "test".
it :: T.Text -> E.Test a -> E.Test a
it = test
-- | Skip the given test(s). A synonym for "_test".
_it :: T.Text -> E.Test a -> E.Test a
_it = _test
-- | Name and group a list of tests. Combines easytest's "scope" and "tests".
tests :: T.Text -> [E.Test ()] -> E.Test ()
tests name = E.scope name . EasyTest.tests
-- | Skip the given list of tests, with the same type signature as "group".
_tests :: T.Text -> [E.Test ()] -> E.Test ()
_tests _name = (E.skip >>) . EasyTest.tests
-- | Run some easytests, returning True if there was a problem. Catches ExitCode.
-- With arguments, runs only tests in the scope named by the first argument
-- (case sensitive).
-- If there is a second argument, it should be an integer and will be used
-- as the seed for randomness.
runEasyTests :: [String] -> E.Test () -> IO Bool
runEasyTests args easytests = (do
case args of
[] -> E.run easytests
[a] -> E.runOnly (T.pack a) easytests
a:b:_ -> do
case readMay b :: Maybe Int of
Nothing -> error' "the second argument should be an integer (a seed for easytest)"
Just seed -> E.rerunOnly seed (T.pack a) easytests
return False
)
`catch` (\(_::ExitCode) -> return True)
-- | Given a stateful, runnable-in-Identity-monad parser, input text, and expected parse result,
-- make an easytest Test that parses the text and compares the result,
-- showing a nice failure message if either step fails.
expectParseEq :: (Monoid st, Eq a, Show a) => StateT st (ParsecT CustomErr T.Text Identity) a -> T.Text -> a -> E.Test ()
expectParseEq parser input expected = do
let ep = runIdentity $ parseWithState mempty parser input
either (fail.("parse error at "++).parseErrorPretty) (expectEq' expected) ep
-- | Given a stateful, runnable-in-IO-monad parser, input text, and expected parse result,
-- make an easytest Test that parses the text and compares the result,
-- showing a nice failure message if either step fails.
expectParseEqIO :: (Monoid st, Eq a, Show a) => StateT st (ParsecT CustomErr T.Text IO) a -> T.Text -> a -> E.Test ()
expectParseEqIO parser input expected = do
ep <- E.io $ runParserT (evalStateT parser mempty) "" input
either (fail.("parse error at "++).parseErrorPretty) (expectEq' expected) ep
-- | Like easytest's expectEq, but pretty-prints the values in failure output.
expectEq' :: (Eq a, Show a, HasCallStack) => a -> a -> E.Test ()
expectEq' x y = if x == y then E.ok else E.crash $
"expected:\n" <> T.pack (pshow x) <> "\nbut got:\n" <> T.pack (pshow y) <> "\n"
-- * HUnit helpers
-- | Get a Test's label, or the empty string.
testName :: HUnit.Test -> String
testName :: U.Test -> String
testName (TestLabel n _) = n
testName _ = ""
-- | Flatten a Test containing TestLists into a list of single tests.
flattenTests :: HUnit.Test -> [HUnit.Test]
flattenTests :: U.Test -> [U.Test]
flattenTests (TestLabel _ t@(TestList _)) = flattenTests t
flattenTests (TestList ts) = concatMap flattenTests ts
flattenTests t = [t]
-- | Filter TestLists in a Test, recursively, preserving the structure.
filterTests :: (HUnit.Test -> Bool) -> HUnit.Test -> HUnit.Test
filterTests :: (U.Test -> Bool) -> U.Test -> U.Test
filterTests p (TestLabel l ts) = TestLabel l (filterTests p ts)
filterTests p (TestList ts) = TestList $ filter (any p . flattenTests) $ map (filterTests p) ts
filterTests _ t = t
@ -67,17 +156,18 @@ assertParseEqual' parse expected =
(\actual -> assertEqual (unlines ["expected: " ++ show expected, " but got: " ++ show actual]) expected actual)
$ runIdentity parse
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
---- | 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).
runHunitTests :: [String] -> HUnit.Test -> IO Bool
runHunitTests :: [String] -> U.Test -> IO Bool
runHunitTests args hunittests = do
let ts =
(case args of
@ -89,7 +179,7 @@ runHunitTests args hunittests = do
where
-- | Like runTestTT but prints to stdout.
runTestTTStdout t = do
(counts, 0) <- HUnit.runTestText (putTextToHandle stdout True) t
(counts, 0) <- U.runTestText (putTextToHandle stdout True) t
return counts
-- matchedTests opts ts
@ -146,66 +236,3 @@ runHunitTests args hunittests = do
-- -- 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"
-- * easytest helpers
-- | Name the given test(s). A more readable synonym for scope.
test :: T.Text -> EasyTest.Test a -> EasyTest.Test a
test = scope
-- | Skip the given test(s), with the same type signature as test.
_test :: T.Text -> EasyTest.Test a -> EasyTest.Test a
_test _name = (skip >>)
-- | Name the given test(s). Another synonym for test.
it :: T.Text -> EasyTest.Test a -> EasyTest.Test a
it = test
-- | Name the given test(s). Another synonym for _test.
_it :: T.Text -> EasyTest.Test a -> EasyTest.Test a
_it = _test
-- | Run some easytests, returning True if there was a problem. Catches ExitCode.
-- With arguments, runs only tests in the scope named by the first argument
-- (case sensitive).
-- If there is a second argument, it should be an integer and will be used
-- as the seed for randomness.
runEasyTests :: [String] -> EasyTest.Test () -> IO Bool
runEasyTests args easytests = (do
case args of
[] -> EasyTest.run easytests
[a] -> EasyTest.runOnly (T.pack a) easytests
a:b:_ -> do
case readMay b :: Maybe Int of
Nothing -> error' "the second argument should be an integer (a seed for easytest)"
Just seed -> EasyTest.rerunOnly seed (T.pack a) easytests
return False
)
`catch` (\(_::ExitCode) -> return True)
-- | Given a stateful, runnable-in-Identity-monad parser, input text, and expected parse result,
-- make an easytest Test that parses the text and compares the result,
-- showing a nice failure message if either step fails.
expectParseEq :: (Monoid st, Eq a, Show a) => StateT st (ParsecT CustomErr T.Text Identity) a -> T.Text -> a -> EasyTest.Test ()
expectParseEq parser input expected = do
let ep = runIdentity $ parseWithState mempty parser input
either (fail.("parse error at "++).parseErrorPretty) (expectEq' expected) ep
-- | Given a stateful, runnable-in-IO-monad parser, input text, and expected parse result,
-- make an easytest Test that parses the text and compares the result,
-- showing a nice failure message if either step fails.
expectParseEqIO :: (Monoid st, Eq a, Show a) => StateT st (ParsecT CustomErr T.Text IO) a -> T.Text -> a -> EasyTest.Test ()
expectParseEqIO parser input expected = do
ep <- io $ runParserT (evalStateT parser mempty) "" input
either (fail.("parse error at "++).parseErrorPretty) (expectEq' expected) ep
-- | Like easytest's expectEq, but pretty-prints the values in failure output.
expectEq' :: (Eq a, Show a, HasCallStack) => a -> a -> EasyTest.Test ()
expectEq' x y = if x == y then ok else crash $
"expected:\n" <> T.pack (pshow x) <> "\nbut got:\n" <> T.pack (pshow y) <> "\n"
-- * misc
printParseError :: (Show a) => a -> IO ()
printParseError e = do putStr "parse error at "; print e

View File

@ -57,7 +57,6 @@ module Hledger.Utils.Text
tests_Hledger_Utils_Text
)
where
import Test.HUnit
-- import Data.Char
import Data.List
@ -72,6 +71,7 @@ import qualified Data.Text as T
-- import Hledger.Utils.Parse
-- import Hledger.Utils.Regex
import Hledger.Utils.String (charWidth)
import Hledger.Utils.Test
-- lowercase, uppercase :: String -> String
-- lowercase = map toLower

View File

@ -6,7 +6,6 @@
{-# LANGUAGE OverloadedStrings #-}
import EasyTest
import Hledger
main :: IO ()

View File

@ -9,13 +9,13 @@ module Hledger.UI (
tests_Hledger_UI
)
where
import Test.HUnit
import Hledger.UI.Main
import Hledger.UI.UIOptions
import Hledger.UI.Theme
import Test.HUnit as U
tests_Hledger_UI :: Test
tests_Hledger_UI :: U.Test
tests_Hledger_UI = TestList
[
-- tests_Hledger_UI_Main

View File

@ -8,12 +8,11 @@ module Hledger.Web
, tests_Hledger_Web
) where
import Test.HUnit
import Hledger.Web.WebOptions
import Hledger.Web.Main
import Test.HUnit as U
tests_Hledger_Web :: Test
tests_Hledger_Web :: U.Test
tests_Hledger_Web = TestList
[
-- tests_Hledger_Web_WebOptions

View File

@ -66,7 +66,6 @@ module Hledger.Cli.CliOptions (
-- -- * Convenience re-exports
-- module Data.String.Here,
-- module System.Console.CmdArgs.Explicit,
-- module Test.HUnit
)
where
@ -96,7 +95,6 @@ import System.Directory
import System.Environment
import System.Exit (exitSuccess)
import System.FilePath
import Test.HUnit
import Text.Megaparsec
import Text.Megaparsec.Char
@ -709,7 +707,6 @@ getDirectoryContentsSafe d =
-- tests
tests_Hledger_Cli_CliOptions :: Test
tests_Hledger_Cli_CliOptions = TestList
[
]

View File

@ -51,7 +51,6 @@ import qualified Data.Text as T
import Data.Time.Calendar
import System.Console.CmdArgs.Explicit as C
import System.Exit
import Test.HUnit as HUnit
import Hledger
import Hledger.Cli.CliOptions

View File

@ -26,7 +26,6 @@ import Data.Monoid
-- import Data.Text (Text)
import qualified Data.Text as T
import System.Console.CmdArgs.Explicit as C
import Test.HUnit
import Hledger
import Prelude hiding (putStrLn)

View File

@ -120,7 +120,7 @@ showHelp = hPutStr stderr $ unlines [
-- most similar recent transaction in the journal.
getAndAddTransactions :: EntryState -> IO ()
getAndAddTransactions es@EntryState{..} = (do
mt <- runInputT (setComplete noCompletion defaultSettings) (run $ haskeline $ confirmedTransactionWizard es)
mt <- runInputT (setComplete noCompletion defaultSettings) (System.Console.Wizard.run $ haskeline $ confirmedTransactionWizard es)
case mt of
Nothing -> fail "urk ?"
Just t -> do

View File

@ -259,7 +259,6 @@ import qualified Data.Text.Lazy as TL
import System.Console.CmdArgs.Explicit as C
import Lucid as L
import Text.CSV
import Test.HUnit
import Text.Printf (printf)
import Text.Tabular as T
--import Text.Tabular.AsciiWide

View File

@ -13,7 +13,6 @@ module Hledger.Cli.Commands.Balancesheet (
import Data.String.Here
import System.Console.CmdArgs.Explicit
import Test.HUnit
import Hledger
import Hledger.Cli.CliOptions
@ -56,7 +55,6 @@ balancesheetmode = compoundBalanceCommandMode balancesheetSpec
balancesheet :: CliOpts -> Journal -> IO ()
balancesheet = compoundBalanceCommand balancesheetSpec
tests_Hledger_Cli_Commands_Balancesheet :: Test
tests_Hledger_Cli_Commands_Balancesheet = TestList
[
]

View File

@ -16,7 +16,6 @@ module Hledger.Cli.Commands.Cashflow (
import Data.String.Here
import System.Console.CmdArgs.Explicit
import Test.HUnit
import Hledger
import Hledger.Cli.CliOptions
@ -53,7 +52,6 @@ cashflowmode = compoundBalanceCommandMode cashflowSpec
cashflow :: CliOpts -> Journal -> IO ()
cashflow = compoundBalanceCommand cashflowSpec
tests_Hledger_Cli_Commands_Cashflow :: Test
tests_Hledger_Cli_Commands_Cashflow = TestList
[
]

View File

@ -11,7 +11,6 @@ import Data.String.Here
import Hledger
import Hledger.Cli.CliOptions
import System.Console.CmdArgs.Explicit
import Test.HUnit
import Text.Printf
-- checkdatesmode :: Mode RawOpts
@ -80,7 +79,6 @@ checkTransactions compare ts =
then acc{fa_previous=Just current}
else acc{fa_error=Just current}
tests_Hledger_Cli_Commands_Checkdates :: Test
tests_Hledger_Cli_Commands_Checkdates = TestList
[
]

View File

@ -13,7 +13,6 @@ module Hledger.Cli.Commands.Incomestatement (
import Data.String.Here
import System.Console.CmdArgs.Explicit
import Test.HUnit
import Hledger
import Hledger.Cli.CliOptions
@ -56,7 +55,6 @@ incomestatementmode = compoundBalanceCommandMode incomestatementSpec
incomestatement :: CliOpts -> Journal -> IO ()
incomestatement = compoundBalanceCommand incomestatementSpec
tests_Hledger_Cli_Commands_Incomestatement :: Test
tests_Hledger_Cli_Commands_Incomestatement = TestList
[
]

View File

@ -18,7 +18,6 @@ where
import Data.Text (Text)
import qualified Data.Text as T
import System.Console.CmdArgs.Explicit
import Test.HUnit
import Text.CSV
import Hledger

View File

@ -21,7 +21,6 @@ import Data.Maybe
import qualified Data.Text as T
import System.Console.CmdArgs.Explicit
import Text.CSV
import Test.HUnit
import Hledger
import Hledger.Cli.CliOptions
@ -201,6 +200,5 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
(balfirstline:balrest) = take numlines $ replicate (numlines - ballen) "" ++ ballines -- balance amount is bottom-aligned
spacer = replicate (totalwidth - (amtwidth + 2 + balwidth)) ' '
tests_Hledger_Cli_Commands_Register :: Test
tests_Hledger_Cli_Commands_Register = TestList
tests_postingsReportAsText

View File

@ -25,7 +25,6 @@ module Hledger.Cli.Utils
readFileStrictly,
pivotByOpts,
anonymiseByOpts,
Test(TestList),
)
where
import Control.Exception as C
@ -47,7 +46,6 @@ import System.FilePath ((</>), splitFileName, takeDirectory)
import System.Info (os)
import System.Process (readProcessWithExitCode)
import System.Time (ClockTime, getClockTime, diffClockTimes, TimeDiff(TimeDiff))
import Test.HUnit
import Text.Printf
import Text.Regex.TDFA ((=~))