License | BSD3 |
---|---|
Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Automatic tests for servant API against OpenApi spec.
Synopsis
- validateEveryToJSON :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => proxy api -> Spec
- validateEveryToJSONWithPatternChecker :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => (Pattern -> Text -> Bool) -> proxy api -> Spec
Documentation
:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) | |
=> proxy api | Servant API. |
-> Spec |
Verify that every type used with
content type in a servant API
has compatible JSON
and ToJSON
instances using ToSchema
.validateToJSON
NOTE:
does not perform string pattern validation.
See validateEveryToJSON
.validateEveryToJSONWithPatternChecker
will produce one validateEveryToJSON
specification for every type in the API.
Each type only gets one test, even if it occurs multiple times in the API.prop
>>>
data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
>>>
newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
>>>
instance ToJSON User
>>>
instance ToSchema User
>>>
instance ToSchema UserId
>>>
instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
>>>
type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
>>>
hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)
ToJSON matches ToSchema User ... UserId ... Finished in ... seconds 2 examples, 0 failures
For the test to compile all body types should have the following instances:
andToJSON
are used to perform the validation;ToSchema
is used to name the test for each type;Typeable
is used to display value for whichShow
does not satisfyToJSON
.ToSchema
is used to arbitrarily generate values.Arbitrary
If any of the instances is missing, you'll get a descriptive type error:
>>>
data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
>>>
instance ToJSON Contact
>>>
instance ToSchema Contact
>>>
type ContactAPI = Get '[JSON] Contact
>>>
hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
... ...No instance for (Arbitrary Contact) ... arising from a use of ‘validateEveryToJSON’ ...
validateEveryToJSONWithPatternChecker Source #
:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) | |
=> (Pattern -> Text -> Bool) |
|
-> proxy api | Servant API. |
-> Spec |
Verify that every type used with
content type in a servant API
has compatible JSON
and ToJSON
instances using ToSchema
.validateToJSONWithPatternChecker
For validation without patterns see
.validateEveryToJSON