module Data.API.Tools.JSONTests
(
jsonTestsTool
, cborTestsTool
, cborToJSONTestsTool
, jsonToCBORTestsTool
, jsonGenericValueTestsTool
, cborGenericValueTestsTool
, prop_decodesTo
, prop_decodesTo'
, prop_resultsMatchRoundtrip
, prop_cborRoundtrip
, prop_cborToJSON
, prop_jsonToCBOR
) where
import Data.API.JSON
import Data.API.JSONToCBOR
import Data.API.Tools.Combinators
import Data.API.Tools.Datatypes
import Data.API.TH
import Data.API.Types
import Data.API.Value
import qualified Data.Aeson as JS
import Codec.Serialise
import Data.Binary.Serialise.CBOR.JSON ()
import Language.Haskell.TH
import Test.QuickCheck
import Test.QuickCheck.Property as QCProperty
import Prelude
jsonTestsTool :: Name -> APITool
jsonTestsTool = testsTool 'prop_resultsMatchRoundtrip
cborTestsTool :: Name -> APITool
cborTestsTool = testsTool 'prop_cborRoundtrip
testsTool :: Name -> Name -> APITool
testsTool prop_nm nm = simpleTool $ \ api -> simpleSigD nm [t| [(String, Property)] |] (props api)
where
props api = listE $ map (generateProp prop_nm) [ an | ThNode an <- api ]
generateProp :: Name -> APINode -> ExpQ
generateProp prop_nm an = [e| ($ty, property ($(varE prop_nm) :: $(nodeT an) -> Bool)) |]
where
ty = typeNameE $ anName an
cborToJSONTestsTool :: Name -> Name -> APITool
cborToJSONTestsTool = schemaTestsTool 'prop_cborToJSON
jsonToCBORTestsTool :: Name -> Name -> APITool
jsonToCBORTestsTool = schemaTestsTool 'prop_jsonToCBOR
jsonGenericValueTestsTool :: Name -> Name -> APITool
jsonGenericValueTestsTool = schemaTestsTool 'prop_jsonGeneric
cborGenericValueTestsTool :: Name -> Name -> APITool
cborGenericValueTestsTool = schemaTestsTool 'prop_cborGeneric
schemaTestsTool :: Name -> Name -> Name -> APITool
schemaTestsTool prop_nm api_nm nm = simpleTool $ \ api -> simpleSigD nm [t| [(String, Property)] |] (props api)
where
props api = listE $ map genProp [ an | ThNode an <- api ]
genProp an = [e| ($ty, property ($(varE prop_nm) $(varE api_nm) tn :: $(nodeT an) -> QCProperty.Result)) |]
where
tn = anName an
ty = typeNameE $ anName an
prop_decodesTo :: forall a . (Eq a, FromJSONWithErrs a)
=> JS.Value -> a -> Bool
prop_decodesTo v x = case fromJSONWithErrs v :: Either [(JSONError, Position)] a of
Right y | x == y -> True
_ -> False
prop_decodesTo' :: forall a . (Eq a, FromJSONWithErrs a)
=> ParseFlags -> JS.Value -> a -> Bool
prop_decodesTo' pf v x = case fromJSONWithErrs' pf v :: Either [(JSONError, Position)] a of
Right y | x == y -> True
_ -> False
prop_resultsMatchRoundtrip :: forall a . (Eq a, JS.ToJSON a, FromJSONWithErrs a )
=> a -> Bool
prop_resultsMatchRoundtrip x = prop_decodesTo (JS.toJSON x) x
prop_cborRoundtrip :: forall a . (Eq a, Serialise a)
=> a -> Bool
prop_cborRoundtrip x = deserialise (serialise x) == x
prop_cborToJSON :: forall a . (Eq a, Serialise a, JS.ToJSON a)
=> API -> TypeName -> a -> QCProperty.Result
prop_cborToJSON api tn x
| v1 == v2 = succeeded
| otherwise = failed { QCProperty.reason = "Post-processed: " ++ show v1
++ "\nDirect JSON: " ++ show v2 }
where
v1 = deserialiseJSONWithSchema api tn (serialise x)
v2 = JS.toJSON x
prop_jsonToCBOR :: forall a . (Eq a, Serialise a, JS.ToJSON a)
=> API -> TypeName -> a -> QCProperty.Result
prop_jsonToCBOR api tn x
| e1 == e2 = succeeded
| otherwise = failed { QCProperty.reason = "Failed with JSON: " ++ show v
++ "\nGeneric serialisation: " ++ show e1
++ "\nDirect serialisation: " ++ show e2 }
where
v = JS.toJSON x
e1 = serialiseJSONWithSchema api tn v
e2 = serialise x