{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Servant.OpenApi.Internal.Test where
import Data.Aeson (ToJSON (..))
import qualified Data.Aeson.Encode.Pretty as P
import qualified Data.ByteString.Lazy as BSL
import Data.OpenApi (Pattern, ToSchema, toSchema)
import Data.OpenApi.Schema.Validation
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Typeable
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck (Arbitrary, Property, counterexample, property)
import Servant.API
import Servant.OpenApi.Internal.TypeLevel
validateEveryToJSON
:: forall proxy api .
TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema])
(BodyTypes JSON api)
=> proxy api
-> Spec
validateEveryToJSON :: forall (proxy :: * -> *) api.
TMap
(Every '[Typeable, Show, Arbitrary, ToJSON, ToSchema])
(BodyTypes JSON api) =>
proxy api -> Spec
validateEveryToJSON proxy api
_ = forall (p :: [* -> Constraint] -> *) (p'' :: [*] -> *)
(cs :: [* -> Constraint]) (xs :: [*]).
TMap (Every (Typeable : Show : Arbitrary : cs)) xs =>
p cs -> (forall x. EveryTF cs x => x -> Property) -> p'' xs -> Spec
props
(forall {k} (t :: k). Proxy t
Proxy :: Proxy [ToJSON, ToSchema])
(Maybe String -> Property
maybeCounterExample forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(ToJSON a, ToSchema a) =>
(a -> [String]) -> a -> Maybe String
prettyValidateWith forall a. (ToJSON a, ToSchema a) => a -> [String]
validateToJSON)
(forall {k} (t :: k). Proxy t
Proxy :: Proxy (BodyTypes JSON api))
validateEveryToJSONWithPatternChecker :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) =>
(Pattern -> Text -> Bool)
-> proxy api
-> Spec
validateEveryToJSONWithPatternChecker :: forall (proxy :: * -> *) api.
TMap
(Every '[Typeable, Show, Arbitrary, ToJSON, ToSchema])
(BodyTypes JSON api) =>
(Pattern -> Pattern -> Bool) -> proxy api -> Spec
validateEveryToJSONWithPatternChecker Pattern -> Pattern -> Bool
checker proxy api
_ = forall (p :: [* -> Constraint] -> *) (p'' :: [*] -> *)
(cs :: [* -> Constraint]) (xs :: [*]).
TMap (Every (Typeable : Show : Arbitrary : cs)) xs =>
p cs -> (forall x. EveryTF cs x => x -> Property) -> p'' xs -> Spec
props
(forall {k} (t :: k). Proxy t
Proxy :: Proxy [ToJSON, ToSchema])
(Maybe String -> Property
maybeCounterExample forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(ToJSON a, ToSchema a) =>
(a -> [String]) -> a -> Maybe String
prettyValidateWith (forall a.
(ToJSON a, ToSchema a) =>
(Pattern -> Pattern -> Bool) -> a -> [String]
validateToJSONWithPatternChecker Pattern -> Pattern -> Bool
checker))
(forall {k} (t :: k). Proxy t
Proxy :: Proxy (BodyTypes JSON api))
props :: forall p p'' cs xs. TMap (Every (Typeable ': Show ': Arbitrary ': cs)) xs =>
p cs
-> (forall x. EveryTF cs x => x -> Property)
-> p'' xs
-> Spec
props :: forall (p :: [* -> Constraint] -> *) (p'' :: [*] -> *)
(cs :: [* -> Constraint]) (xs :: [*]).
TMap (Every (Typeable : Show : Arbitrary : cs)) xs =>
p cs -> (forall x. EveryTF cs x => x -> Property) -> p'' xs -> Spec
props p cs
_ forall x. EveryTF cs x => x -> Property
f p'' xs
px = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Spec]
specs
where
specs :: [Spec]
specs :: [Spec]
specs = forall a (cs :: [* -> Constraint]) (p :: [* -> Constraint] -> *)
(p'' :: [*] -> *) (xs :: [*]).
TMap (Every cs) xs =>
p cs
-> (forall x (p' :: * -> *). Every cs x => p' x -> a)
-> p'' xs
-> [a]
tmapEvery (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Typeable ': Show ': Arbitrary ': cs)) forall (p' :: * -> *) a.
(EveryTF cs a, Typeable a, Show a, Arbitrary a) =>
p' a -> Spec
aprop p'' xs
px
aprop :: forall p' a. (EveryTF cs a, Typeable a, Show a, Arbitrary a) => p' a -> Spec
aprop :: forall (p' :: * -> *) a.
(EveryTF cs a, Typeable a, Show a, Arbitrary a) =>
p' a -> Spec
aprop p' a
_ = forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop (forall a. Show a => a -> String
show (forall a. Typeable a => a -> TypeRep
typeOf (forall a. HasCallStack => a
undefined :: a))) (forall x. EveryTF cs x => x -> Property
f :: a -> Property)
prettyValidateWith
:: forall a. (ToJSON a, ToSchema a)
=> (a -> [ValidationError]) -> a -> Maybe String
prettyValidateWith :: forall a.
(ToJSON a, ToSchema a) =>
(a -> [String]) -> a -> Maybe String
prettyValidateWith a -> [String]
f a
x =
case a -> [String]
f a
x of
[] -> forall a. Maybe a
Nothing
[String]
errors -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
[ String
"Validation against the schema fails:"
, [String] -> String
unlines (forall a b. (a -> b) -> [a] -> [b]
map (String
" * " forall a. [a] -> [a] -> [a]
++) [String]
errors)
, String
"JSON value:"
, Value -> String
ppJSONString Value
json
, String
""
, String
"OpenApi Schema:"
, Value -> String
ppJSONString (forall a. ToJSON a => a -> Value
toJSON Schema
schema)
]
where
ppJSONString :: Value -> String
ppJSONString = Text -> String
TL.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encodePretty
json :: Value
json = forall a. ToJSON a => a -> Value
toJSON a
x
schema :: Schema
schema = forall a. ToSchema a => Proxy a -> Schema
toSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
maybeCounterExample :: Maybe String -> Property
maybeCounterExample :: Maybe String -> Property
maybeCounterExample Maybe String
Nothing = forall prop. Testable prop => prop -> Property
property Bool
True
maybeCounterExample (Just String
s) = forall prop. Testable prop => String -> prop -> Property
counterexample String
s (forall prop. Testable prop => prop -> Property
property Bool
False)
encodePretty :: ToJSON a => a -> BSL.ByteString
encodePretty :: forall a. ToJSON a => a -> ByteString
encodePretty = forall a. ToJSON a => Config -> a -> ByteString
P.encodePretty' forall a b. (a -> b) -> a -> b
$ Config
P.defConfig { confCompare :: Pattern -> Pattern -> Ordering
P.confCompare = forall a. Ord a => a -> a -> Ordering
P.compare }