{-# LANGUAGE DeriveDataTypeable, BangPatterns #-}
module Test.Tasty.HUnit.Steps (testCaseSteps) where
import Control.Applicative
import Control.Exception
import Data.IORef
import Data.List (foldl')
import Data.Typeable (Typeable)
import Prelude
import Test.Tasty.HUnit.Orig
import Test.Tasty.Providers
import Test.Tasty.Runners (getTime)
import Text.Printf (printf)
newtype TestCaseSteps = TestCaseSteps ((String -> IO ()) -> Assertion)
deriving Typeable
instance IsTest TestCaseSteps where
run _ (TestCaseSteps assertionFn) _ = do
ref <- newIORef []
let
stepFn :: String -> IO ()
stepFn msg = do
tme <- getTime
atomicModifyIORef ref (\l -> ((tme,msg):l, ()))
hunitResult <- (Right <$> assertionFn stepFn) `catches`
[ Handler (\(HUnitFailure mbloc errMsg) -> return $ Left (prependLocation mbloc errMsg))
, Handler (\(SomeException ex) -> return $ Left (show ex))
]
endTime <- getTime
maxMsgLength <- foldl' max 0 . map (length . snd) <$> readIORef ref
let msgFormat = "%-" ++ show (min maxMsgLength 62) ++ "s (%.02fs)"
msgs <- snd . foldl'
(\(lastTime, acc) (curTime, msg) ->
let !duration = lastTime - curTime
!msg' = if duration >= 0.01 then printf msgFormat msg duration else msg
in (curTime, msg':acc))
(endTime, [])
<$> readIORef ref
return $
case hunitResult of
Right {} -> testPassed (unlines msgs)
Left errMsg -> testFailed $
if null msgs
then
errMsg
else
unlines $
msgs ++ map (" " ++) (lines errMsg)
testOptions = return []
testCaseSteps :: TestName -> ((String -> IO ()) -> Assertion) -> TestTree
testCaseSteps name = singleTest name . TestCaseSteps