define/run tests anywhere

This commit is contained in:
Simon Michael 2007-03-12 09:38:02 +00:00
parent abc3ed32cf
commit 2b696b8f0d
4 changed files with 23 additions and 34 deletions

1
TODO
View File

@ -13,7 +13,6 @@ speed
profile, refactor, optimize
basic features
-f -
print
!include
, in thousands

View File

@ -3,15 +3,11 @@ module Tests
where
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec
import Test.QuickCheck
import Test.HUnit
-- trying to make "*Tests> test" work
-- hiding (test)
--import qualified Test.HUnit (Test.HUnit.test)
import Options
import Models
import Parse
import Utils
-- sample data
@ -260,20 +256,15 @@ parseEquals parsed other =
-- hunit tests
tests = let t l f = TestLabel l $ TestCase f in TestList
[
t "test_ledgertransaction" test_ledgertransaction
, t "test_ledgerentry" test_ledgerentry
, t "test_autofillEntry" test_autofillEntry
, t "test_expandAccountNames" test_expandAccountNames
, t "test_ledgerAccountNames" test_ledgerAccountNames
tests = runTestTT $ test [
test_ledgertransaction
, test_ledgerentry
, test_autofillEntry
, test_expandAccountNames
, test_ledgerAccountNames
, 2 @=? 2
]
tests2 = Test.HUnit.test
[
"test1" ~: assertEqual "2 equals 2" 2 2
]
test_ledgertransaction :: Assertion
test_ledgertransaction =
assertParseEqual transaction1 (parse' ledgertransaction transaction1_str)
@ -300,7 +291,7 @@ test_ledgerAccountNames =
-- quickcheck properties
props =
props = mapM quickCheck
[
parse' ledgertransaction transaction1_str `parseEquals`
(Transaction "expenses:food:dining" (Amount "$" 10))

View File

@ -2,18 +2,20 @@ module Utils (
module Utils,
module Data.List,
module Data.Tree,
module Debug.Trace,
module Text.Printf,
module Text.Regex,
quickCheck,
module Debug.Trace,
module Test.QuickCheck,
module Test.HUnit
)
where
import Data.List
import Data.Tree
import Debug.Trace
import Test.QuickCheck (quickCheck)
import Text.Printf
import Text.Regex
import Debug.Trace
import Test.QuickCheck hiding (test, Testable)
import Test.HUnit
splitAtElement :: Eq a => a -> [a] -> [[a]]
@ -24,6 +26,8 @@ splitAtElement e l =
where
(first,rest) = break (e==) l'
-- testing support
-- tree tools

View File

@ -28,11 +28,7 @@ hledger
module Main
where
import System
import System.Environment (withArgs) -- for testing in old hugs
import Test.HUnit (runTestTT)
import Test.QuickCheck (quickCheck)
import Text.ParserCombinators.Parsec (ParseError)
import Debug.Trace
import Options
import Models
@ -49,7 +45,7 @@ main = do
where run cmd opts acctpats descpats
| cmd `isPrefixOf` "register" = register opts acctpats descpats
| cmd `isPrefixOf` "balance" = balance opts acctpats descpats
| cmd `isPrefixOf` "test" = test
| cmd `isPrefixOf` "test" = selftest
| otherwise = putStr usage
-- commands
@ -75,13 +71,12 @@ balance opts acctpats _ = do
([],False) -> 1
otherwise -> 9999
test :: IO ()
test = do
hcounts <- runTestTT tests
qcounts <- mapM quickCheck props
selftest :: IO ()
selftest = do
Tests.tests
Tests.props
-- Amount.tests
return ()
where showHunitCounts c =
reverse $ tail $ reverse ("passed " ++ (unwords $ drop 5 $ words (show c)))
-- utils