module Test.HUnitPlus.Base(
Test(..),
TestInstance(..),
TestSuite(..),
Testable(..),
(~=?),
(~?=),
(~:),
(~?),
Assertion,
assertSuccess,
assertFailure,
abortFailure,
abortError,
assertBool,
assertString,
assertStringWithPrefix,
assertEqual,
Assertable(..),
(@=?),
(@?=),
(@?),
executeTest,
logAssert,
logFailure,
logError,
withPrefix,
getErrors,
getFailures
) where
import Control.Exception hiding (assert)
import Data.Foldable
import Data.IORef
import Data.Typeable
import Data.Word
import Distribution.TestSuite
import Prelude hiding (concat, sum, sequence_)
import System.IO.Unsafe
import System.TimeIt
import Test.HUnitPlus.Reporting
data TestException =
TestException {
teError :: !Bool,
teMsg :: !String
} deriving (Show, Typeable)
instance Exception TestException
data TestInfo =
TestInfo {
tiAsserts :: !Word,
tiEvents :: ![(Word, String)],
tiIgnoreResult :: !Bool,
tiPrefix :: !String
}
errorCode :: Word
errorCode = 0
failureCode :: Word
failureCode = 1
sysOutCode :: Word
sysOutCode = 2
sysErrCode :: Word
sysErrCode = 3
testinfo :: IORef TestInfo
testinfo = unsafePerformIO $ newIORef undefined
executeTest :: Reporter us
-> State
-> us
-> IO Progress
-> IO (Double, State, us)
executeTest rep @ Reporter { reporterCaseProgress = reportCaseProgress }
ss usInitial runTest =
let
finishTestCase time us action =
let
handleExceptions :: SomeException -> IO Progress
handleExceptions ex =
case fromException ex of
Just TestException { teError = True, teMsg = msg } ->
do
logError msg
return (Finished (Error msg))
Just TestException { teError = False, teMsg = msg } ->
do
logFailure msg
return (Finished (Fail msg))
Nothing ->
do
return (Finished (Error ("Uncaught exception in test: " ++
show ex)))
caughtAction = catch action handleExceptions
in do
(inctime, progress) <- timeItT caughtAction
case progress of
Progress msg nextAction ->
do
usNext <- reportCaseProgress msg ss us
finishTestCase (time + inctime) usNext nextAction
Finished res -> return (res, us, time + inctime)
in do
resetTestInfo
(res, usFinished, time) <- finishTestCase 0 usInitial runTest
(ssReported, usReported) <- reportTestInfo res rep ss usFinished
return (time, ssReported, usReported)
reportTestInfo :: Result -> Reporter us -> State -> us -> IO (State, us)
reportTestInfo result Reporter { reporterError = reportError,
reporterFailure = reportFailure,
reporterSystemOut = reportSystemOut,
reporterSystemErr = reportSystemErr }
ss @ State { stCounts = c @ Counts { cAsserts = asserts,
cFailures = failures,
cErrors = errors } }
initialUs =
let
handleEvent (us, hasFailure, hasError) (code, msg)
| code == errorCode =
do
us' <- reportError msg ss us
return (us', hasFailure, True)
| code == failureCode =
do
us' <- reportFailure msg ss us
return (us', True, hasError)
| code == sysOutCode =
do
us' <- reportSystemOut msg ss us
return (us', hasFailure, hasError)
| code == sysErrCode =
do
us' <- reportSystemErr msg ss us
return (us', hasFailure, hasError)
| otherwise = fail ("Internal error: bad code " ++ show code)
in do
TestInfo { tiAsserts = currAsserts,
tiEvents = currEvents,
tiIgnoreResult = ignoreRes } <- readIORef testinfo
(eventsUs, hasFailure, hasError) <-
foldlM handleEvent (initialUs, False, False) (reverse currEvents)
case result of
Error msg | not ignoreRes ->
do
finalUs <- reportError msg ss eventsUs
return $! (ss { stCounts =
c { cAsserts = asserts + fromIntegral currAsserts,
cErrors = errors + 1 } },
finalUs)
Fail msg | not ignoreRes ->
do
finalUs <- reportFailure msg ss eventsUs
return $! (ss { stCounts =
c { cAsserts = asserts + fromIntegral currAsserts,
cFailures = failures + 1 } },
finalUs)
_ -> return $! (ss { stCounts =
c { cAsserts = asserts + fromIntegral currAsserts,
cFailures =
if hasFailure
then failures + 1
else failures,
cErrors =
if hasError
then errors + 1
else errors } },
eventsUs)
ignoreResult :: IO ()
ignoreResult = modifyIORef testinfo (\t -> t { tiIgnoreResult = True })
resetTestInfo :: IO ()
resetTestInfo = writeIORef testinfo TestInfo { tiAsserts = 0,
tiEvents = [],
tiIgnoreResult = False,
tiPrefix = "" }
withPrefix :: String -> IO () -> IO ()
withPrefix prefix c =
do
t @ TestInfo { tiPrefix = oldprefix } <- readIORef testinfo
writeIORef testinfo t { tiPrefix = prefix ++ oldprefix }
c
modifyIORef testinfo (\t' -> t' { tiPrefix = oldprefix })
logAssert :: IO ()
logAssert = modifyIORef testinfo (\t -> t { tiAsserts = tiAsserts t + 1 })
logError :: String -> IO ()
logError msg =
modifyIORef testinfo (\t -> t { tiEvents = (errorCode, tiPrefix t ++ msg) :
tiEvents t })
logFailure :: String -> IO ()
logFailure msg =
modifyIORef testinfo (\t -> t { tiEvents = (failureCode, tiPrefix t ++ msg) :
tiEvents t })
getFailures :: IO (Maybe String)
getFailures =
do
TestInfo { tiEvents = events } <- readIORef testinfo
case map snd (filter ((== failureCode) . fst) events) of
[] -> return $ Nothing
fails -> return $ (Just (concat (reverse fails)))
getErrors :: IO (Maybe String)
getErrors =
do
TestInfo { tiEvents = events } <- readIORef testinfo
case map snd (filter ((== errorCode) . fst) events) of
[] -> return $ Nothing
errors -> return $ (Just (concat (reverse errors)))
type Assertion = IO ()
assertFailure :: String
-> Assertion
assertFailure msg = logAssert >> logFailure msg
assertSuccess :: Assertion
assertSuccess = logAssert
abortError :: String -> Assertion
abortError msg = throw TestException { teError = True, teMsg = msg }
abortFailure :: String -> Assertion
abortFailure msg = throw TestException { teError = False, teMsg = msg }
assertBool :: String
-> Bool
-> Assertion
assertBool msg b = if b then assertSuccess else assertFailure msg
assertString :: String
-> Assertion
assertString = assertStringWithPrefix ""
assertStringWithPrefix :: String
-> String
-> Assertion
assertStringWithPrefix prefix s = assertBool (prefix ++ s) (null s)
assertEqual :: (Eq a, Show a)
=> String
-> a
-> a
-> Assertion
assertEqual preface expected actual =
let
msg = (if null preface then "" else preface ++ "\n") ++
"expected: " ++ show expected ++ "\nbut got: " ++ show actual
in
assertBool msg (actual == expected)
class Assertable t where
assertWithMsg :: String -> t -> Assertion
assert :: t -> Assertion
assert = assertWithMsg ""
instance Assertable () where
assertWithMsg _ = return
instance Assertable Bool where
assertWithMsg msg = assertBool msg
instance Assertable Result where
assertWithMsg _ Pass = assertSuccess
assertWithMsg "" (Error errstr) = logError errstr
assertWithMsg prefix (Error errstr) = logError (prefix ++ errstr)
assertWithMsg "" (Fail failstr) = assertFailure failstr
assertWithMsg prefix (Fail failstr) = assertFailure (prefix ++ failstr)
instance Assertable Progress where
assertWithMsg msg (Progress _ cont) = assertWithMsg msg cont
assertWithMsg msg (Finished res) = assertWithMsg msg res
instance (ListAssertable t) => Assertable [t] where
assertWithMsg msg = listAssert msg
instance (Assertable t) => Assertable (IO t) where
assertWithMsg msg t = t >>= assertWithMsg msg
class ListAssertable t where
listAssert :: String -> [t] -> Assertion
instance ListAssertable Char where
listAssert msg = assertStringWithPrefix msg
instance ListAssertable Assertion where
listAssert msg asserts = withPrefix msg (sequence_ asserts)
infix 1 @?, @=?, @?=
(@?) :: (Assertable t) =>
t
-> String
-> Assertion
predi @? msg = assertWithMsg msg predi
(@=?) :: (Eq a, Show a)
=> a
-> a
-> Assertion
expected @=? actual = assertEqual "" expected actual
(@?=) :: (Eq a, Show a)
=> a
-> a
-> Assertion
actual @?= expected = assertEqual "" expected actual
data TestSuite =
TestSuite {
suiteName :: !String,
suiteConcurrently :: !Bool,
suiteOptions :: [(String, String)],
suiteTests :: [Test]
}
syntheticName :: String
syntheticName = "__synthetic__"
wrapTest :: IO a -> IO Progress
wrapTest t =
do
ignoreResult
_ <- t
checkTestInfo
checkTestInfo :: IO Progress
checkTestInfo =
do
errors <- getErrors
case errors of
Nothing ->
do
failures <- getFailures
case failures of
Nothing -> return $ (Finished Pass)
Just failstr -> return $ (Finished (Fail failstr))
Just errstr -> return $ (Finished (Error errstr))
class Testable t where
testNameTags :: String -> [String] -> t -> Test
testName :: String -> t -> Test
testName testname t = testNameTags testname [] t
testTags :: [String] -> t -> Test
testTags tagset t = testNameTags syntheticName tagset t
test :: Testable t => t -> Test
test t = testNameTags syntheticName [] t
instance Testable Test where
testNameTags newname newtags g @ Group { groupTests = testlist } =
g { groupName = newname, groupTests = map (testTags newtags) testlist }
testNameTags newname newtags (Test t @ TestInstance { tags = oldtags }) =
Test t { name = newname, tags = newtags ++ oldtags }
testNameTags newname newtags (ExtraOptions opts t) =
ExtraOptions opts (testNameTags newname newtags t)
testTags newtags g @ Group { groupTests = testlist } =
g { groupTests = map (testTags newtags) testlist }
testTags newtags (Test t @ TestInstance { tags = oldtags }) =
Test t { tags = newtags ++ oldtags }
testTags newtags (ExtraOptions opts t) =
ExtraOptions opts (testTags newtags t)
testName newname g @ Group {} = g { groupName = newname }
testName newname (Test t) = Test t { name = newname }
testName newname (ExtraOptions opts t) =
ExtraOptions opts (testName newname t)
test = id
instance (Assertable t) => Testable (IO t) where
testNameTags testname testtags t =
Test TestInstance { name = testname, tags = testtags,
run = wrapTest (t >>= assert),
options = [], setOption = undefined }
instance (Testable t) => Testable [t] where
testNameTags testname testtags ts =
Group { groupName = testname, groupTests = map (testTags testtags) ts,
concurrently = True }
infix 1 ~?, ~=?, ~?=
infixr 0 ~:
(~?) :: (Assertable t)
=> t
-> String
-> Test
predi ~? msg = test (predi @? msg)
(~=?) :: (Eq a, Show a)
=> a
-> a
-> Test
expected ~=? actual = test (expected @=? actual)
(~?=) :: (Eq a, Show a)
=> a
-> a
-> Test
actual ~?= expected = test (actual @?= expected)
(~:) :: (Testable t) => String -> t -> Test
label ~: t = testName label t