{-# LANGUAGE FlexibleInstances #-}
module Test.Framework.TestTypes (
TestID, Test(..), TestOptions(..), AssertionWithTestOptions(..), WithTestOptions(..),
TestSuite(..), TestSort(..),
TestPath(..), GenFlatTest(..), FlatTest, TestFilter,
testPathToList, flatName, finalName, prefixName, defaultTestOptions, withOptions, historyKey,
TR, TestState(..), initTestState, TestConfig(..), TestOutput(..),
ReportAllTests, ReportGlobalStart, ReportTestStart, ReportTestResult, ReportGlobalResults, ReportGlobalResultsArg(..),
TestReporter(..), emptyTestReporter, attachCallStack, CallStack,
TestResult(..), FlatTestResult, Milliseconds, RunResult(..)
) where
import Test.Framework.Location
import Test.Framework.Colors
import Test.Framework.History
import Test.Framework.TestInterface
import Control.Monad.RWS
import System.IO
import Data.Maybe
import qualified Data.List as List
import qualified Data.Text as T
type TestID = String
data TestSort = UnitTest | QuickCheckTest | BlackBoxTest
deriving (Eq,Show,Read)
data TestOptions = TestOptions {
to_parallel :: Bool
}
deriving (Eq,Show,Read)
defaultTestOptions :: TestOptions
defaultTestOptions = TestOptions {
to_parallel = True
}
data WithTestOptions a = WithTestOptions {
wto_options :: TestOptions
, wto_payload :: a
}
deriving (Eq,Show,Read)
withOptions :: (TestOptions -> TestOptions) -> a -> WithTestOptions a
withOptions f x = WithTestOptions (f defaultTestOptions) x
class AssertionWithTestOptions a where
testOptions :: a -> TestOptions
assertion :: a -> Assertion
instance AssertionWithTestOptions (IO a) where
testOptions _ = defaultTestOptions
assertion io = io >> return ()
instance AssertionWithTestOptions (WithTestOptions (IO a)) where
testOptions (WithTestOptions opts _) = opts
assertion (WithTestOptions _ io) = io >> return ()
data Test = BaseTest TestSort TestID (Maybe Location) TestOptions Assertion
| CompoundTest TestSuite
data TestSuite = TestSuite TestID [Test]
| AnonTestSuite [Test]
data TestPath = TestPathBase TestID
| TestPathCompound (Maybe TestID) TestPath
deriving (Show)
testPathToList :: TestPath -> [Maybe TestID]
testPathToList (TestPathBase i) = [Just i]
testPathToList (TestPathCompound mi p) =
mi : testPathToList p
flatName :: TestPath -> String
flatName p =
flatNameFromList (testPathToList p)
flatNameFromList :: [Maybe TestID] -> String
flatNameFromList l =
List.intercalate ":" (map (fromMaybe "") l)
finalName :: TestPath -> String
finalName (TestPathBase i) = i
finalName (TestPathCompound _ p) = finalName p
prefixName :: TestPath -> String
prefixName path =
let l = case reverse (testPathToList path) of
[] -> []
(_:xs) -> reverse xs
in flatNameFromList l
data GenFlatTest a
= FlatTest
{ ft_sort :: TestSort
, ft_path :: TestPath
, ft_location :: Maybe Location
, ft_payload :: a
}
historyKey :: GenFlatTest a -> T.Text
historyKey ft = T.pack (flatName (ft_path ft))
type FlatTest = GenFlatTest (WithTestOptions Assertion)
type TestFilter = FlatTest -> Bool
type CallStack = [(Maybe String, Location)]
data RunResult
= RunResult
{ rr_result :: TestResult
, rr_location :: Maybe Location
, rr_callers :: CallStack
, rr_message :: ColorString
, rr_wallTimeMs :: Milliseconds
, rr_timeout :: Bool
}
attachCallStack :: ColorString -> CallStack -> ColorString
attachCallStack msg callStack =
case reverse callStack of
[] -> msg
l -> ensureNewlineColorString msg +++
noColor (unlines (map formatCallStackElem l))
where
formatCallStackElem (mMsg, loc) =
" called from " ++ showLoc loc ++ (case mMsg of
Nothing -> ""
Just s -> " (" ++ s ++ ")")
type FlatTestResult = GenFlatTest RunResult
data TestState = TestState { ts_results :: [FlatTestResult]
, ts_index :: Int
}
initTestState :: TestState
initTestState = TestState [] 0
type TR = RWST TestConfig () TestState IO
data TestOutput = TestOutputHandle Handle Bool
| TestOutputSplitted FilePath
deriving (Show, Eq)
data TestConfig
= TestConfig
{ tc_quiet :: Bool
, tc_threads :: Maybe Int
, tc_shuffle :: Bool
, tc_output :: TestOutput
, tc_outputXml :: Maybe FilePath
, tc_filter :: TestFilter
, tc_reporters :: [TestReporter]
, tc_useColors :: Bool
, tc_historyFile :: FilePath
, tc_history :: TestHistory
, tc_sortByPrevTime :: Bool
, tc_failFast :: Bool
, tc_timeoutIsSuccess :: Bool
, tc_maxSingleTestTime :: Maybe Milliseconds
, tc_prevFactor :: Maybe Double
, tc_repeat :: Int
}
instance Show TestConfig where
showsPrec prec tc =
showParen (prec > 0) $
showString "TestConfig { " .
showString "tc_quiet=" . showsPrec 1 (tc_quiet tc) .
showString ", tc_threads=" . showsPrec 1 (tc_threads tc) .
showString ", tc_shuffle=" . showsPrec 1 (tc_shuffle tc) .
showString ", tc_output=" . showsPrec 1 (tc_output tc) .
showString ", tc_outputXml=" . showsPrec 1 (tc_outputXml tc) .
showString ", tc_filter=<filter>" .
showString ", tc_reporters=" . showsPrec 1 (tc_reporters tc) .
showString ", tc_useColors=" . showsPrec 1 (tc_useColors tc) .
showString ", tc_historyFile=" . showsPrec 1 (tc_historyFile tc) .
showString ", tc_history=" . showsPrec 1 (tc_history tc) .
showString ", tc_sortByPrevTime=" . showsPrec 1 (tc_sortByPrevTime tc) .
showString ", tc_failFast=" . showsPrec 1 (tc_failFast tc) .
showString ", tc_timeoutIsSuccess=" . showsPrec 1 (tc_timeoutIsSuccess tc) .
showString ", tc_maxSingleTestTime=" . showsPrec 1 (tc_maxSingleTestTime tc) .
showString ", tc_prevFactor=" . showsPrec 1 (tc_prevFactor tc) .
showString ", tc_repeat=" . showsPrec 1 (tc_repeat tc) .
showString " }"
data TestReporter
= TestReporter
{ tr_id :: String
, tr_reportAllTests :: ReportAllTests
, tr_reportGlobalStart :: ReportGlobalStart
, tr_reportTestStart :: ReportTestStart
, tr_reportTestResult :: ReportTestResult
, tr_reportGlobalResults :: ReportGlobalResults
}
emptyTestReporter :: String -> TestReporter
emptyTestReporter id =
TestReporter
{ tr_id = id
, tr_reportAllTests = \_ -> return ()
, tr_reportGlobalStart = \_ -> return ()
, tr_reportTestStart = \_ -> return ()
, tr_reportTestResult = \_ -> return ()
, tr_reportGlobalResults = \_ -> return ()
}
instance Show TestReporter where
showsPrec _ x = showString (tr_id x)
instance Eq TestReporter where
x == y = (tr_id x) == (tr_id y)
type ReportAllTests = [FlatTest] -> TR ()
type ReportGlobalStart = [FlatTest] -> TR ()
type ReportTestStart = FlatTest -> TR ()
type ReportTestResult = FlatTestResult -> TR ()
data ReportGlobalResultsArg
= ReportGlobalResultsArg
{ rgra_timeMs :: Milliseconds
, rgra_passed :: [FlatTestResult]
, rgra_pending :: [FlatTestResult]
, rgra_failed :: [FlatTestResult]
, rgra_errors :: [FlatTestResult]
, rgra_timedOut :: [FlatTestResult]
, rgra_filtered :: [FlatTest]
}
type ReportGlobalResults = ReportGlobalResultsArg -> TR ()