| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.QuickCheck
Contents
Description
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.
Synopsis
- serverSatisfies :: HasGenRequest a => Proxy a -> BaseUrl -> Args -> Predicates -> Expectation
- not500 :: ResponsePredicate
- notLongerThan :: Integer -> RequestPredicate
- onlyJsonObjects :: ResponsePredicate
- honoursAcceptHeader :: RequestPredicate
- notAllowedContainsAllowHeader :: RequestPredicate
- unauthorizedContainsWWWAuthenticate :: ResponsePredicate
- getsHaveLastModifiedHeader :: RequestPredicate
- getsHaveCacheControlHeader :: RequestPredicate
- headsHaveCacheControlHeader :: RequestPredicate
- createContainsValidLocation :: RequestPredicate
- htmlIncludesDoctype :: ResponsePredicate
- (<%>) :: 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
- jsonEquality :: JsonEq 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 {- replay :: Maybe (QCGen, Int)
- maxSuccess :: Int
- maxDiscardRatio :: Int
- maxSize :: Int
- chatty :: Bool
- maxShrinks :: Int
 
- data Proxy (t :: k) :: forall k. k -> Type = 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
honoursAcceptHeader :: RequestPredicate Source #
- RFC Compliance
When a request contains an Accept header, the server must either return
 content in one of the requested representations, or respond with 406 Not
 Acceptable.
This function checks that every *successful* response has a Content-Type
 header that matches the Accept header. It does *not* check that the server
 matches the quality descriptions of the Accept header correctly.
References:
- Acceptheader: RFC 2616 Section 14.1
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:
- Allowheader: 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-Authenticateheader: RFC 7235 Section 4.1
Since 0.0.0.0
getsHaveLastModifiedHeader :: RequestPredicate Source #
- Optional
The Last-Modified header represents the time a resource was last
 modified. It is used to drive caching and conditional requests.
When using this mechanism, the server adds the Last-Modified header to
 responses. Clients may then make requests with the If-Modified-Since
 header to conditionally request resources. If the resource has not
 changed since that date, the server responds with a status code of 304
 (Not Modified) without a response body.
The Last-Modified header can also be used in conjunction with the
 If-Unmodified-Since header to drive optimistic concurrency.
The Last-Modified date must be in RFC 822 format.
References:
- 304 Not Modified: RFC 7232 Section 4.1
- Last-Modified header: RFC 7232 Section 2.2
- If-Modified-Since header: RFC 7232 Section 3.3
- If-Unmodified-Since header: RFC 7232 Section 3.4
- Date format: RFC 2616 Section 3.3
Since 0.0.2.1
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-Controlheader: 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
Html Predicates
htmlIncludesDoctype :: ResponsePredicate Source #
- RFC Compliance
- An HTML
- document will start with exactly this string: html
This function checks that HTML documents (those with `Content-Type: text/html...`)
 include a DOCTYPE declaration at the top. We do not enforce capital case for the string DOCTYPE.
References:
- HTML5 Doctype: RFC 7992 Section 6.1 Since 0.3.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 #
Instances
newtype ResponsePredicate Source #
A predicate that depends only on the response.
Since 0.0.0.0
Constructors
| ResponsePredicate | |
| Fields 
 | |
Instances
newtype RequestPredicate Source #
A predicate that depends on both the request and the response.
Since 0.0.0.0
Constructors
| RequestPredicate | |
| Fields 
 | |
Instances
Equality testing
serversEqual :: HasGenRequest a => Proxy a -> BaseUrl -> BaseUrl -> Args -> ResponseEquality ByteString -> Expectation Source #
Check that the two servers running under the provided BaseUrls 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 ResponseEqualitys
bodyEquality :: Eq b => ResponseEquality b Source #
ByteString Eq instance over the response body.
Since 0.0.0.0
jsonEquality :: JsonEq b => ResponseEquality b Source #
Equality as Value. This means that if two bodies are equal as JSON
 (e.g., insignificant whitespace difference) they are considered equal.
Since 0.0.3.0
allEquality :: Eq b => ResponseEquality b Source #
Response equality type
newtype ResponseEquality b Source #
Constructors
| ResponseEquality | |
| Fields 
 | |
Instances
| Semigroup (ResponseEquality b) Source # | |
| Defined in Servant.QuickCheck.Internal.Equality Methods (<>) :: ResponseEquality b -> ResponseEquality b -> ResponseEquality b # sconcat :: NonEmpty (ResponseEquality b) -> ResponseEquality b # stimes :: Integral b0 => b0 -> ResponseEquality b -> ResponseEquality b # | |
| Monoid (ResponseEquality b) Source # | |
| Defined in Servant.QuickCheck.Internal.Equality Methods mempty :: ResponseEquality b # mappend :: ResponseEquality b -> ResponseEquality b -> ResponseEquality b # mconcat :: [ResponseEquality b] -> ResponseEquality b # | |
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.
Constructors
| BaseUrl | |
| Fields 
 | |
Instances
| Eq BaseUrl | |
| Data BaseUrl | |
| Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaseUrl -> c BaseUrl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaseUrl # toConstr :: BaseUrl -> Constr # dataTypeOf :: BaseUrl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BaseUrl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaseUrl) # gmapT :: (forall b. Data b => b -> b) -> BaseUrl -> BaseUrl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r # gmapQ :: (forall d. Data d => d -> u) -> BaseUrl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BaseUrl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # | |
| Ord BaseUrl | |
| Defined in Servant.Client.Core.BaseUrl | |
| Show BaseUrl | |
| Generic BaseUrl | |
| Lift BaseUrl | |
| ToJSON BaseUrl | 
 | 
| Defined in Servant.Client.Core.BaseUrl | |
| ToJSONKey BaseUrl | 
 | 
| Defined in Servant.Client.Core.BaseUrl | |
| FromJSON BaseUrl | 
 | 
| FromJSONKey BaseUrl | |
| Defined in Servant.Client.Core.BaseUrl Methods | |
| NFData BaseUrl | |
| Defined in Servant.Client.Core.BaseUrl | |
| type Rep BaseUrl | |
| Defined in Servant.Client.Core.BaseUrl type Rep BaseUrl = D1 (MetaData "BaseUrl" "Servant.Client.Core.BaseUrl" "servant-client-core-0.17-6TEb4JOolq16hAUWK9fzoL" False) (C1 (MetaCons "BaseUrl" PrefixI True) ((S1 (MetaSel (Just "baseUrlScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Just "baseUrlHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "baseUrlPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "baseUrlPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) | |
URI scheme to use
Instances
| Eq Scheme | |
| Data Scheme | |
| Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme # toConstr :: Scheme -> Constr # dataTypeOf :: Scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) # gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # | |
| Ord Scheme | |
| Show Scheme | |
| Generic Scheme | |
| Lift Scheme | |
| type Rep Scheme | |
Args specifies arguments to the QuickCheck driver
Constructors
| Args | |
| Fields 
 | |
data Proxy (t :: k) :: forall k. k -> Type #
Proxy is a type that holds no data, but has a phantom parameter of
 arbitrary type (or even kind). Its use is to provide type information, even
 though there is no value available of that type (or it may be too costly to
 create one).
Historically, Proxy :: Proxy a'undefined :: a' idiom.
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy | 
Instances
| Generic1 (Proxy :: k -> Type) | |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| FromJSON1 (Proxy :: Type -> Type) | |
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Defined in Data.Functor.Classes | |
| Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Defined in Data.Functor.Classes | |
| Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Hashable1 (Proxy :: Type -> Type) | |
| Defined in Data.Hashable.Class | |
| Bounded (Proxy t) | Since: base-4.7.0.0 | 
| Enum (Proxy s) | Since: base-4.7.0.0 | 
| Eq (Proxy s) | Since: base-4.7.0.0 | 
| Ord (Proxy s) | Since: base-4.7.0.0 | 
| Read (Proxy t) | Since: base-4.7.0.0 | 
| Show (Proxy s) | Since: base-4.7.0.0 | 
| Ix (Proxy s) | Since: base-4.7.0.0 | 
| Defined in Data.Proxy | |
| Generic (Proxy t) | |
| Semigroup (Proxy s) | Since: base-4.9.0.0 | 
| Monoid (Proxy s) | Since: base-4.7.0.0 | 
| Hashable (Proxy a) | |
| Defined in Data.Hashable.Class | |
| FromJSON (Proxy a) | |
| type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 | 
| type Rep (Proxy t) | Since: base-4.6.0.0 |