{-# LANGUAGE OverloadedStrings #-}
module Test.Framework.JsonOutput (
TestStartEventObj, TestEndEventObj, TestListObj, TestObj, TestResultsObj,
mkTestStartEventObj, mkTestEndEventObj, mkTestListObj, mkTestResultsObj,
decodeObj, HTFJsonObj
) where
import Test.Framework.TestTypes
import Test.Framework.Location
import Test.Framework.Colors
import Test.Framework.TestInterface
import qualified Data.Aeson as J
import Data.Aeson ((.=))
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Char8 as BSLC
import qualified Data.Text as T
class J.ToJSON a => HTFJsonObj a
data TestStartEventObj
= TestStartEventObj
{ TestStartEventObj -> TestObj
ts_test :: TestObj }
instance J.ToJSON TestStartEventObj where
toJSON :: TestStartEventObj -> Value
toJSON TestStartEventObj
ts =
[Pair] -> Value
J.object [Key
"type" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"test-start"
,Key
"test" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TestObj -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestStartEventObj -> TestObj
ts_test TestStartEventObj
ts)]
instance HTFJsonObj TestStartEventObj
data TestEndEventObj
= TestEndEventObj
{ TestEndEventObj -> TestObj
te_test :: TestObj
, TestEndEventObj -> TestResult
te_result :: TestResult
, TestEndEventObj -> HtfStack
te_stack :: HtfStack
, TestEndEventObj -> Text
te_message :: T.Text
, TestEndEventObj -> Int
te_wallTimeMs :: Int
, TestEndEventObj -> Bool
te_timedOut :: Bool
}
instance J.ToJSON TestEndEventObj where
toJSON :: TestEndEventObj -> Value
toJSON TestEndEventObj
te =
[Pair] -> Value
J.object [Key
"type" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"test-end"
,Key
"test" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TestObj -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestEndEventObj -> TestObj
te_test TestEndEventObj
te)
,Key
"location" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Location -> Value
forall a. ToJSON a => a -> Value
J.toJSON (HtfStack -> Maybe Location
failureLocationFromStack (TestEndEventObj -> HtfStack
te_stack TestEndEventObj
te))
,Key
"callers" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=
[Value] -> Value
forall a. ToJSON a => a -> Value
J.toJSON ((HtfStackEntry -> Value) -> [HtfStackEntry] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map (\HtfStackEntry
entry -> [Pair] -> Value
J.object [Key
"location" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Location -> Value
forall a. ToJSON a => a -> Value
J.toJSON (HtfStackEntry -> Location
hse_location HtfStackEntry
entry)
,Key
"message" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe String -> Value
forall a. ToJSON a => a -> Value
J.toJSON (HtfStackEntry -> Maybe String
hse_message HtfStackEntry
entry)])
(HtfStack -> [HtfStackEntry]
restCallStack (TestEndEventObj -> HtfStack
te_stack TestEndEventObj
te)))
,Key
"result" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TestResult -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestEndEventObj -> TestResult
te_result TestEndEventObj
te)
,Key
"message" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestEndEventObj -> Text
te_message TestEndEventObj
te)
,Key
"wallTime" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestEndEventObj -> Int
te_wallTimeMs TestEndEventObj
te)
,Key
"timedOut" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestEndEventObj -> Bool
te_timedOut TestEndEventObj
te)]
instance HTFJsonObj TestEndEventObj
data TestListObj
= TestListObj
{ TestListObj -> [TestObj]
tlm_tests :: [TestObj]
}
instance J.ToJSON TestListObj where
toJSON :: TestListObj -> Value
toJSON TestListObj
tl =
[Pair] -> Value
J.object [Key
"type" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"test-list"
,Key
"tests" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [TestObj] -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestListObj -> [TestObj]
tlm_tests TestListObj
tl)]
instance HTFJsonObj TestListObj
data TestResultsObj
= TestResultsObj
{ TestResultsObj -> Int
tr_wallTimeMs :: Int
, TestResultsObj -> Int
tr_passed :: Int
, TestResultsObj -> Int
tr_pending :: Int
, TestResultsObj -> Int
tr_failed :: Int
, TestResultsObj -> Int
tr_errors :: Int
, TestResultsObj -> Int
tr_timedOut :: Int
, TestResultsObj -> Int
tr_filtered :: Int
}
instance J.ToJSON TestResultsObj where
toJSON :: TestResultsObj -> Value
toJSON TestResultsObj
r = [Pair] -> Value
J.object [Key
"type" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"test-results"
,Key
"passed" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_passed TestResultsObj
r)
,Key
"pending" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_pending TestResultsObj
r)
,Key
"failures" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_failed TestResultsObj
r)
,Key
"errors" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_errors TestResultsObj
r)
,Key
"timedOut" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_timedOut TestResultsObj
r)
,Key
"filtered" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_filtered TestResultsObj
r)
,Key
"wallTime" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestResultsObj -> Int
tr_wallTimeMs TestResultsObj
r)]
instance HTFJsonObj TestResultsObj
data TestObj
= TestObj
{ TestObj -> String
to_flatName :: String
, TestObj -> TestPath
to_path :: TestPath
, TestObj -> Maybe Location
to_location :: Maybe Location
, TestObj -> TestSort
to_sort :: TestSort
}
instance J.ToJSON TestObj where
toJSON :: TestObj -> Value
toJSON TestObj
t = [Pair] -> Value
J.object ([Key
"flatName" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= String -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestObj -> String
to_flatName TestObj
t)
,Key
"path" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TestPath -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestObj -> TestPath
to_path TestObj
t)
,Key
"sort" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TestSort -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestObj -> TestSort
to_sort TestObj
t)] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
(case TestObj -> Maybe Location
to_location TestObj
t of
Just Location
loc -> [Key
"location" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Location -> Value
forall a. ToJSON a => a -> Value
J.toJSON Location
loc]
Maybe Location
Nothing -> []))
instance J.ToJSON TestPath where
toJSON :: TestPath -> Value
toJSON TestPath
p = [Maybe String] -> Value
forall a. ToJSON a => a -> Value
J.toJSON (TestPath -> [Maybe String]
testPathToList TestPath
p)
instance J.ToJSON TestSort where
toJSON :: TestSort -> Value
toJSON TestSort
s =
case TestSort
s of
TestSort
UnitTest -> Text -> Value
J.String Text
"unit-test"
TestSort
QuickCheckTest -> Text -> Value
J.String Text
"quickcheck-property"
TestSort
BlackBoxTest -> Text -> Value
J.String Text
"blackbox-test"
instance J.ToJSON Location where
toJSON :: Location -> Value
toJSON Location
loc = [Pair] -> Value
J.object [Key
"file" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= String -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Location -> String
fileName Location
loc)
,Key
"line" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Location -> Int
lineNumber Location
loc)]
mkTestObj :: GenFlatTest a -> String -> TestObj
mkTestObj :: forall a. GenFlatTest a -> String -> TestObj
mkTestObj GenFlatTest a
ft String
flatName =
String -> TestPath -> Maybe Location -> TestSort -> TestObj
TestObj String
flatName (GenFlatTest a -> TestPath
forall a. GenFlatTest a -> TestPath
ft_path GenFlatTest a
ft) (GenFlatTest a -> Maybe Location
forall a. GenFlatTest a -> Maybe Location
ft_location GenFlatTest a
ft) (GenFlatTest a -> TestSort
forall a. GenFlatTest a -> TestSort
ft_sort GenFlatTest a
ft)
mkTestStartEventObj :: FlatTest -> String -> TestStartEventObj
mkTestStartEventObj :: FlatTest -> String -> TestStartEventObj
mkTestStartEventObj FlatTest
ft String
flatName =
TestObj -> TestStartEventObj
TestStartEventObj (FlatTest -> String -> TestObj
forall a. GenFlatTest a -> String -> TestObj
mkTestObj FlatTest
ft String
flatName)
mkTestEndEventObj :: FlatTestResult -> String -> TestEndEventObj
mkTestEndEventObj :: FlatTestResult -> String -> TestEndEventObj
mkTestEndEventObj FlatTestResult
ftr String
flatName =
let r :: RunResult
r = FlatTestResult -> RunResult
forall a. GenFlatTest a -> a
ft_payload FlatTestResult
ftr
msg :: Text
msg = ColorString -> Bool -> Text
renderColorString (RunResult -> ColorString
rr_message RunResult
r) Bool
False
in TestObj
-> TestResult -> HtfStack -> Text -> Int -> Bool -> TestEndEventObj
TestEndEventObj (FlatTestResult -> String -> TestObj
forall a. GenFlatTest a -> String -> TestObj
mkTestObj FlatTestResult
ftr String
flatName) (RunResult -> TestResult
rr_result RunResult
r) (RunResult -> HtfStack
rr_stack RunResult
r)
Text
msg (RunResult -> Int
rr_wallTimeMs RunResult
r) (RunResult -> Bool
rr_timeout RunResult
r)
mkTestListObj :: [(FlatTest, String)] -> TestListObj
mkTestListObj :: [(FlatTest, String)] -> TestListObj
mkTestListObj [(FlatTest, String)]
l =
[TestObj] -> TestListObj
TestListObj (((FlatTest, String) -> TestObj)
-> [(FlatTest, String)] -> [TestObj]
forall a b. (a -> b) -> [a] -> [b]
map (\(FlatTest
ft, String
flatName) -> FlatTest -> String -> TestObj
forall a. GenFlatTest a -> String -> TestObj
mkTestObj FlatTest
ft String
flatName) [(FlatTest, String)]
l)
mkTestResultsObj :: ReportGlobalResultsArg -> TestResultsObj
mkTestResultsObj :: ReportGlobalResultsArg -> TestResultsObj
mkTestResultsObj ReportGlobalResultsArg
arg =
TestResultsObj
{ tr_wallTimeMs :: Int
tr_wallTimeMs = ReportGlobalResultsArg -> Int
rgra_timeMs ReportGlobalResultsArg
arg
, tr_passed :: Int
tr_passed = [FlatTestResult] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTestResult]
rgra_passed ReportGlobalResultsArg
arg)
, tr_pending :: Int
tr_pending = [FlatTestResult] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTestResult]
rgra_pending ReportGlobalResultsArg
arg)
, tr_failed :: Int
tr_failed = [FlatTestResult] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTestResult]
rgra_failed ReportGlobalResultsArg
arg)
, tr_errors :: Int
tr_errors = [FlatTestResult] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTestResult]
rgra_errors ReportGlobalResultsArg
arg)
, tr_timedOut :: Int
tr_timedOut = [FlatTestResult] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTestResult]
rgra_timedOut ReportGlobalResultsArg
arg)
, tr_filtered :: Int
tr_filtered = [FlatTest] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ReportGlobalResultsArg -> [FlatTest]
rgra_filtered ReportGlobalResultsArg
arg)
}
decodeObj :: HTFJsonObj a => a -> BSL.ByteString
decodeObj :: forall a. HTFJsonObj a => a -> ByteString
decodeObj a
x =
a -> ByteString
forall a. ToJSON a => a -> ByteString
J.encode a
x ByteString -> ByteString -> ByteString
`BSL.append` (String -> ByteString
BSLC.pack String
"\n;;\n")