Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.QuickCheck
provides utilities related to using QuickCheck over an API.
Rather than specifying properties that individual handlers must satisfy,
you can state properties that ought to hold true of the entire API.
While the API must be described with servant
types, the server being
tested itself need not be implemented with servant-server
(or indeed,
written in Haskell).
The documentation of the Useful predicates sections is meant to serve as a set of helpful pointers for learning more about best practices concerning REST APIs.
- serverSatisfies :: HasGenRequest a => Proxy a -> BaseUrl -> Args -> Predicates -> Expectation
- not500 :: ResponsePredicate
- notLongerThan :: Integer -> RequestPredicate
- onlyJsonObjects :: ResponsePredicate
- notAllowedContainsAllowHeader :: RequestPredicate
- unauthorizedContainsWWWAuthenticate :: ResponsePredicate
- getsHaveCacheControlHeader :: RequestPredicate
- headsHaveCacheControlHeader :: RequestPredicate
- createContainsValidLocation :: RequestPredicate
- (<%>) :: JoinPreds a => a -> Predicates -> Predicates
- data Predicates
- newtype ResponsePredicate = ResponsePredicate {
- getResponsePredicate :: Response ByteString -> IO ()
- newtype RequestPredicate = RequestPredicate {
- getRequestPredicate :: Request -> Manager -> IO [Response ByteString]
- serversEqual :: HasGenRequest a => Proxy a -> BaseUrl -> BaseUrl -> Args -> ResponseEquality ByteString -> Expectation
- bodyEquality :: Eq b => ResponseEquality b
- allEquality :: Eq b => ResponseEquality b
- newtype ResponseEquality b = ResponseEquality {
- getResponseEquality :: Response b -> Response b -> Bool
- withServantServer :: HasServer a '[] => Proxy a -> IO (Server a) -> (BaseUrl -> IO r) -> IO r
- withServantServerAndContext :: HasServer a ctx => Proxy a -> Context ctx -> IO (Server a) -> (BaseUrl -> IO r) -> IO r
- defaultArgs :: Args
- data BaseUrl :: * = BaseUrl {}
- data Scheme :: *
- data Args :: * = Args {}
- data Proxy k t :: forall k. k -> * = Proxy
Property testing
serverSatisfies :: HasGenRequest a => Proxy a -> BaseUrl -> Args -> Predicates -> Expectation Source #
Check that a server satisfies the set of properties specified.
Note that, rather than having separate tests for each property you'd like to test, you should generally prefer to combine all properties into a single test. This enables a more parsimonious generation of requests and responses with the same testing depth.
Example usage:
goodAPISpec = describe "my server" $ do it "follows best practices" $ do withServantServer api server $ \burl -> serverSatisfies api burl stdArgs (not500 <%> onlyJsonObjects <%> notAllowedContainsAllowHeader <%> mempty)
Since 0.0.0.0
Predicates
Useful predicates
The predicates below are often useful. Some check RFC compliance; some are best practice, and some are useful to check that APIs follow in-house best-practices. Included in the documentation for each is a list of references to any relevant RFCs and other links, as well as what type of predicate it is (RFC Compliance, Best Practice, Optional).
RFCs distinguish between the force of requirements (e.g. MUST vs. SHOULD). RFC Compliance includes any absolute requirements present in RFCs. The Best Practices includes, in addition to RFC recommendations, recommendations found elsewhere or generally accepted.
not500 :: ResponsePredicate Source #
- Best Practice
500 Internal Server Error
should be avoided - it may represent some
issue with the application code, and it moreover gives the client little
indication of how to proceed or what went wrong.
This function checks that the response code is not 500.
Since 0.0.0.0
notLongerThan :: Integer -> RequestPredicate Source #
- Optional
This function checks that the response from the server does not take longer than the specified number of nanoseconds.
Since 0.0.2.1
onlyJsonObjects :: ResponsePredicate Source #
- Best Practice
Returning anything other than an object when returning JSON is considered bad practice, as:
- it is hard to modify the returned value while maintaining backwards compatibility
- many older tools do not support top-level arrays
- whether top-level numbers, booleans, or strings are valid JSON depends on what RFC you're going by
- there are security issues with top-level arrays
This function checks that any application/json
responses only return JSON
objects (and not arrays, strings, numbers, or booleans) at the top level.
References:
- JSON Grammar: RFC 7159 Section 2
- JSON Grammar: RFC 4627 Section 2
Since 0.0.0.0
notAllowedContainsAllowHeader :: RequestPredicate Source #
- RFC Compliance
When an HTTP request has a method that is not allowed,
a 405 response should be returned. Additionally, it is good practice to
return an Allow
header with the list of allowed methods.
This function checks that every 405 Method Not Allowed
response contains
an Allow
header with a list of standard HTTP methods.
Note that servant
itself does not currently set the Allow
headers.
References:
Allow
header: RFC 2616 Section 14.7- Status 405: RFC 2616 Section 10.4.6
- Servant Allow header issue: Issue #489
Since 0.0.0.0
unauthorizedContainsWWWAuthenticate :: ResponsePredicate Source #
- RFC Compliance
Any 401 Unauthorized
response must include a WWW-Authenticate
header.
This function checks that, if a response has status code 401, it contains a
WWW-Authenticate
header.
References:
WWW-Authenticate
header: RFC 7235 Section 4.1
Since 0.0.0.0
getsHaveCacheControlHeader :: RequestPredicate Source #
- Best Practice
Whether or not a representation should be cached, it is good practice to
have a Cache-Control
header for GET
requests. If the representation
should not be cached, used Cache-Control: no-cache
.
This function checks that GET
responses have Cache-Control
header.
It does NOT currently check that the header is valid.
References:
Cache-Control
header: RFC 7234 Section 5.2
Since 0.0.0.0
createContainsValidLocation :: RequestPredicate Source #
Optional
When creating a new resource, it is good practice to provide a Location
header with a link to the created resource.
This function checks that every 201 Created
response contains a Location
header, and that the link in it responds with a 2XX response code to GET
requests.
This is considered optional because other means of linking to the resource (e.g. via the response body) are also acceptable; linking to the resource in some way is considered best practice.
References:
- 201 Created: RFC 7231 Section 6.3.2
- Location header: RFC 7231 Section 7.1.2
Since 0.0.0.0
Predicate utilities and types
(<%>) :: JoinPreds a => a -> Predicates -> Predicates infixr 6 Source #
Adds a new predicate (either ResponsePredicate
or RequestPredicate
) to
the existing predicates.
not500 <%> onlyJsonObjects <%> empty
Since 0.0.0.0
data Predicates Source #
newtype ResponsePredicate Source #
A predicate that depends only on the response.
Since 0.0.0.0
newtype RequestPredicate Source #
A predicate that depends on both the request and the response.
Since 0.0.0.0
Equality testing
serversEqual :: HasGenRequest a => Proxy a -> BaseUrl -> BaseUrl -> Args -> ResponseEquality ByteString -> Expectation Source #
Check that the two servers running under the provided BaseUrl
s behave
identically by randomly generating arguments (captures, query params, request bodies,
headers, etc.) expected by the server. If, given the same request, the
response is not the same (according to the definition of ==
for the return
datatype), the Expectation
fails, printing the counterexample.
The Int
argument specifies maximum number of test cases to generate and
run.
Evidently, if the behaviour of the server is expected to be non-deterministic, this function may produce spurious failures
Note that only valid requests are generated and tested. As an example of why
this matters, let's say your API specifies that a particular endpoint can
only generate JSON
. serversEqual
will then not generate any requests
with an Accept
header _other_ than application/json
. It may therefore
fail to notice that one application, when the request has Accept:
text/html
, returns a 406 Not Acceptable
HTTP response, and another
returns a 200 Success
, but with application/json
as the content-type.
The fact that only valid requests are tested also means that no endpoints not listed in the API type are tested.
Since 0.0.0.0
Response equality
Often the normal equality of responses is not what we want. For example,
if responses contain a Date
header with the time of the response,
responses will fail to be equal even though they morally are. This datatype
represents other means of checking equality
*** Useful ResponseEquality
s
bodyEquality :: Eq b => ResponseEquality b Source #
ByteString Eq
instance over the response body.
Since 0.0.0.0
allEquality :: Eq b => ResponseEquality b Source #
Response equality type
newtype ResponseEquality b Source #
ResponseEquality | |
|
Test setup helpers
Helpers to setup and teardown servant
servers during tests.
withServantServer :: HasServer a '[] => Proxy a -> IO (Server a) -> (BaseUrl -> IO r) -> IO r Source #
Start a servant application on an open port, run the provided function, then stop the application.
Since 0.0.0.0
withServantServerAndContext :: HasServer a ctx => Proxy a -> Context ctx -> IO (Server a) -> (BaseUrl -> IO r) -> IO r Source #
Like withServantServer
, but allows passing in a Context
to the
application.
Since 0.0.0.0
defaultArgs :: Args Source #
QuickCheck Args
with 1000 rather than 100 test cases.
Since 0.0.0.0
Re-exports
Types and constructors from other packages that are generally needed for
using servant-quickcheck
.
Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.
BaseUrl | |
|
URI scheme to use
Args specifies arguments to the QuickCheck driver
Args | |
|
data Proxy k t :: forall k. k -> * #
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Generic1 (Proxy *) | |
Alternative (Proxy *) | |
MonadPlus (Proxy *) | |
Eq1 (Proxy *) | Since: 4.9.0.0 |
Ord1 (Proxy *) | Since: 4.9.0.0 |
Read1 (Proxy *) | Since: 4.9.0.0 |
Show1 (Proxy *) | Since: 4.9.0.0 |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy k t) | |
Semigroup (Proxy k s) | |
Monoid (Proxy k s) | |
FromJSON (Proxy k a) | |
type Rep1 (Proxy *) | |
type Rep (Proxy k t) | |