2018-10-12 05:51:30 +02:00
|
|
|
|
# How To Test Servant Applications
|
|
|
|
|
|
|
|
|
|
Even with a nicely structured API that passes Haskell's strict type checker,
|
2018-10-12 17:48:25 +02:00
|
|
|
|
it's a good idea to write some tests for your application.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
In this recipe we'll work through some common testing strategies and provide
|
|
|
|
|
examples of utlizing these testing strategies in order to test Servant
|
|
|
|
|
applications.
|
|
|
|
|
|
2018-10-14 19:19:49 +02:00
|
|
|
|
## Testing strategies
|
|
|
|
|
|
|
|
|
|
There are many testing strategies you may wish to employ when testing your
|
|
|
|
|
Servant application, but included below are three common testing patterns:
|
|
|
|
|
|
2018-10-14 20:04:37 +02:00
|
|
|
|
- We'll use `servant-client` to derive client functions and then send valid
|
|
|
|
|
requests to our API, running in another thread. This is great for testing
|
2018-10-14 19:19:49 +02:00
|
|
|
|
that our **business logic** is correctly implemented with only valid HTTP
|
|
|
|
|
requests.
|
|
|
|
|
|
|
|
|
|
- We'll also use `hspec-wai` to make **arbitrary HTTP requests**, in order to
|
|
|
|
|
test how our application may respond to invalid or otherwise unexpected
|
|
|
|
|
requests.
|
|
|
|
|
|
|
|
|
|
- Finally, we can also use `servant-quickcheck` for **whole-API tests**, in order
|
|
|
|
|
to assert that our entire application conforms to **best practices**.
|
|
|
|
|
|
|
|
|
|
## Useful Libraries
|
|
|
|
|
|
|
|
|
|
The following libraries will often come in handy when we decide to test our
|
|
|
|
|
Servant applications:
|
|
|
|
|
|
|
|
|
|
- [hspec](https://hspec.github.io/)
|
|
|
|
|
- [hspec-wai](http://hackage.haskell.org/package/hspec-wai)
|
|
|
|
|
- [QuickCheck](http://hackage.haskell.org/package/QuickCheck)
|
|
|
|
|
- [servant-quickcheck](https://hackage.haskell.org/package/servant-quickcheck)
|
|
|
|
|
|
|
|
|
|
## Imports and Our Testing Module
|
|
|
|
|
|
2018-10-14 20:04:37 +02:00
|
|
|
|
This recipe starts with the following ingredients:
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
{-# LANGUAGE OverloadedStrings, TypeFamilies, DataKinds,
|
|
|
|
|
DeriveGeneric, TypeOperators #-}
|
2018-10-25 22:16:16 +02:00
|
|
|
|
import Prelude ()
|
|
|
|
|
import Prelude.Compat
|
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
import qualified Control.Concurrent as C
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import Control.Concurrent.MVar
|
|
|
|
|
import Control.Exception (bracket)
|
|
|
|
|
import Control.Lens hiding (Context)
|
2018-10-12 05:51:30 +02:00
|
|
|
|
import Data.Aeson
|
|
|
|
|
import Data.Aeson.Lens
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import qualified Data.HashMap.Strict as HM
|
2018-10-25 22:16:16 +02:00
|
|
|
|
import Data.Text (Text, unpack)
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import GHC.Generics
|
2018-10-25 22:16:16 +02:00
|
|
|
|
import Network.HTTP.Client hiding (Proxy)
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import Network.HTTP.Types
|
2018-10-12 05:51:30 +02:00
|
|
|
|
import Network.Wai
|
|
|
|
|
import qualified Network.Wai.Handler.Warp as Warp
|
2018-10-12 17:48:25 +02:00
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
import Servant
|
|
|
|
|
import Servant.Client
|
|
|
|
|
import Servant.Server
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import Servant.QuickCheck
|
|
|
|
|
import Servant.QuickCheck.Internal (serverDoesntSatisfy)
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
import Test.Hspec
|
2018-10-12 17:48:25 +02:00
|
|
|
|
import Test.Hspec.Wai
|
2018-10-12 05:51:30 +02:00
|
|
|
|
import Test.Hspec.Wai.Matcher
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
We're going to produce different `Spec`s that represent different
|
|
|
|
|
aspects of our application, and we'll ask `hspec` to run all of our different
|
|
|
|
|
`Spec`s. This is a common organizational method for testing modules:
|
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
spec :: Spec
|
2018-10-12 17:48:25 +02:00
|
|
|
|
spec = do
|
2018-10-12 05:51:30 +02:00
|
|
|
|
businessLogicSpec
|
|
|
|
|
thirdPartyResourcesSpec
|
|
|
|
|
servantQuickcheckSpec
|
|
|
|
|
```
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
Often, codebases will use `hspec`'s
|
2018-10-12 05:51:30 +02:00
|
|
|
|
[autodiscover pragma](http://hspec.github.io/hspec-discover.html)
|
|
|
|
|
to find all testing modules and `Spec`s inside, but we're going to
|
|
|
|
|
explicitly make a `main` function to run our tests because we have only one
|
|
|
|
|
`spec` defined above:
|
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
main :: IO ()
|
|
|
|
|
main = hspec spec
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
## Testing Your Business Logic
|
|
|
|
|
|
|
|
|
|
Let's say we have an API that looks something like this:
|
|
|
|
|
|
|
|
|
|
```haskell
|
2018-10-12 17:48:25 +02:00
|
|
|
|
data User = User {
|
|
|
|
|
name :: Text
|
|
|
|
|
, user_id :: Integer
|
2018-10-12 05:51:30 +02:00
|
|
|
|
} deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
|
|
instance FromJSON User
|
|
|
|
|
instance ToJSON User
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
type UserApi =
|
2018-10-12 05:51:30 +02:00
|
|
|
|
-- One endpoint: create a user
|
|
|
|
|
"user" :> Capture "userId" Integer :> Post '[JSON] User
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
A real server would likely use a database to store, retrieve, and validate
|
|
|
|
|
users, but we're going to do something really simple merely to have something
|
2018-10-14 19:19:49 +02:00
|
|
|
|
to test. With that said, here's a sample handler, server, and `Application`
|
|
|
|
|
for the endpoint described above:
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
```haskell
|
2018-10-14 19:19:49 +02:00
|
|
|
|
userApp :: Application
|
|
|
|
|
userApp = serve (Proxy :: Proxy UserApi) userServer
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
userServer :: Server UserApi
|
2018-10-12 05:51:30 +02:00
|
|
|
|
userServer = createUser
|
2018-10-12 17:48:25 +02:00
|
|
|
|
|
|
|
|
|
createUser :: Integer -> Handler User
|
|
|
|
|
createUser userId = do
|
|
|
|
|
if userId > 5000
|
|
|
|
|
then pure $ User { name = "some user", user_id = userId }
|
|
|
|
|
else throwError $ err400 { errBody = "userId is too small" }
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
### Strategy 1: Spin Up a Server, Create a Client, Make Some Requests
|
|
|
|
|
|
|
|
|
|
One of the benefits of Servant's type-level DSL for describing APIs is that
|
|
|
|
|
once you have provided a type-level description of your API, you can create
|
|
|
|
|
clients, documentation, or other tools for it somewhat magically.
|
|
|
|
|
|
|
|
|
|
In this case, we'd like to *test* our server, so we can use `servant-client`
|
|
|
|
|
to create a client, after which we'll run our server, and then make requests
|
|
|
|
|
of it and see how it responds.
|
|
|
|
|
|
|
|
|
|
Let's write some tests:
|
|
|
|
|
|
|
|
|
|
```haskell
|
2019-07-16 22:16:59 +02:00
|
|
|
|
withUserApp :: (Warp.Port -> IO ()) -> IO ()
|
2018-10-14 19:19:49 +02:00
|
|
|
|
withUserApp action =
|
2019-07-16 22:16:59 +02:00
|
|
|
|
-- testWithApplication makes sure the action is executed after the server has
|
|
|
|
|
-- started and is being properly shutdown.
|
|
|
|
|
Warp.testWithApplication (pure userApp) action
|
2018-10-14 19:19:49 +02:00
|
|
|
|
|
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
businessLogicSpec :: Spec
|
2018-10-14 19:19:49 +02:00
|
|
|
|
businessLogicSpec =
|
2018-10-14 20:04:37 +02:00
|
|
|
|
-- `around` will start our Server before the tests and turn it off after
|
2019-07-16 22:16:59 +02:00
|
|
|
|
around withUserApp $ do
|
2018-10-14 19:19:49 +02:00
|
|
|
|
-- create a test client function
|
|
|
|
|
let createUser = client (Proxy :: Proxy UserApi)
|
|
|
|
|
-- create a servant-client ClientEnv
|
2019-07-16 22:16:59 +02:00
|
|
|
|
baseUrl <- runIO $ parseBaseUrl "http://localhost"
|
2018-10-14 19:19:49 +02:00
|
|
|
|
manager <- runIO $ newManager defaultManagerSettings
|
2019-07-16 22:16:59 +02:00
|
|
|
|
let clientEnv port = mkClientEnv manager (baseUrl { baseUrlPort = port })
|
2018-10-14 19:19:49 +02:00
|
|
|
|
|
|
|
|
|
-- testing scenarios start here
|
|
|
|
|
describe "POST /user" $ do
|
2019-07-16 22:16:59 +02:00
|
|
|
|
it "should create a user with a high enough ID" $ \port -> do
|
|
|
|
|
result <- runClientM (createUser 50001) (clientEnv port)
|
2018-10-14 19:19:49 +02:00
|
|
|
|
result `shouldBe` (Right $ User { name = "some user", user_id = 50001})
|
2019-07-16 22:16:59 +02:00
|
|
|
|
it "will it fail with a too-small ID?" $ \port -> do
|
|
|
|
|
result <- runClientM (createUser 4999) (clientEnv port)
|
2018-10-14 19:19:49 +02:00
|
|
|
|
result `shouldBe` (Right $ User { name = "some user", user_id = 50001})
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
### Running These Tests
|
|
|
|
|
|
|
|
|
|
Let's run our tests and see what happens:
|
|
|
|
|
|
|
|
|
|
```
|
|
|
|
|
$ cabal new-test all
|
2018-10-12 17:48:25 +02:00
|
|
|
|
POST /user
|
|
|
|
|
should create a user with a high enough ID
|
|
|
|
|
should fail with a too-small ID FAILED [1]
|
|
|
|
|
|
|
|
|
|
Failures:
|
|
|
|
|
|
|
|
|
|
Testing.lhs:129:7:
|
|
|
|
|
1) POST /user should fail with a too-small ID
|
|
|
|
|
expected: Right (User {name = "some user", user_id = 50001})
|
|
|
|
|
but got: Left (FailureResponse (Response {responseStatusCode = Status {statusCode = 400, statusMessage = "Bad Request"}, responseHeaders = fromList [("Transfer-Encoding","chunked"),("Date","Fri, 12 Oct 2018 04:36:22 GMT"),("Server","Warp/3.2.25")], responseHttpVersion = HTTP/1.1, responseBody = "userId is too small"}))
|
|
|
|
|
|
|
|
|
|
To rerun use: --match "/POST /user/should fail with a too-small ID/"
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
Hmm. One passed and one failed! It looks like I *was* expecting a success
|
|
|
|
|
response in the second test, but I actually got a failure. We should fix that,
|
|
|
|
|
but first I'd like to introduce `hspec-wai`, which will give us different
|
|
|
|
|
mechanisms for making requests of our application and validating the responses
|
2018-10-13 02:32:20 +02:00
|
|
|
|
we get. We're also going to spin up a fake Elasticsearch server, so that our
|
|
|
|
|
server can think it's talking to a real database.
|
2018-10-12 17:48:25 +02:00
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
## *Mocking* 3rd Party Resources
|
|
|
|
|
|
|
|
|
|
Often our web applications will need to make their own web
|
|
|
|
|
requests to other 3rd-party applications. These requests provide a lot
|
|
|
|
|
of opportunity for failure and so we'd like to test that the right
|
|
|
|
|
messages and failure values (in addition to success values) are returned
|
|
|
|
|
from our application.
|
|
|
|
|
|
|
|
|
|
### Define the 3rd-Party Resource
|
|
|
|
|
|
|
|
|
|
With Servant's type-level API definitions, assuming you've already defined the
|
|
|
|
|
API you want to mock, it's relatively trivial to create a simple server for
|
|
|
|
|
the purposes of running tests. For instance, consider an API server that needs
|
|
|
|
|
to get data out of Elasticsearch. Let's first define the Elasticsearch server
|
|
|
|
|
and client using Servant API descriptions:
|
|
|
|
|
|
|
|
|
|
```haskell
|
2018-10-12 17:48:25 +02:00
|
|
|
|
type SearchAPI =
|
2018-10-12 05:51:30 +02:00
|
|
|
|
-- We're using Aeson's Generic JSON `Value` to make things easier on
|
|
|
|
|
-- ourselves. We're also representing only one Elasticsearch endpoint:
|
|
|
|
|
-- get item by id
|
|
|
|
|
"myIndex" :> "myDocType" :> Capture "docId" Integer :> Get '[JSON] Value
|
|
|
|
|
|
|
|
|
|
-- Here's our Servant Client function
|
|
|
|
|
getDocument = client (Proxy :: Proxy SearchAPI)
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
-- We can use these helpers when we want to make requests
|
2018-10-12 05:51:30 +02:00
|
|
|
|
-- using our client function
|
|
|
|
|
clientEnv :: Text -> Text -> IO ClientEnv
|
|
|
|
|
clientEnv esHost esPort = do
|
2018-10-12 17:48:25 +02:00
|
|
|
|
baseUrl <- parseBaseUrl $ unpack $ esHost <> ":" <> esPort
|
2018-10-12 05:51:30 +02:00
|
|
|
|
manager <- newManager defaultManagerSettings
|
|
|
|
|
pure $ mkClientEnv manager baseUrl
|
|
|
|
|
|
2019-02-18 19:17:46 +01:00
|
|
|
|
runSearchClient :: Text -> Text -> ClientM a -> IO (Either ClientError a)
|
2018-10-12 05:51:30 +02:00
|
|
|
|
runSearchClient esHost esPort = (clientEnv esHost esPort >>=) . runClientM
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
### Servant Server Example Using this 3rd-Party Resource
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
So we've got an Elasticsearch server and a client to talk to it. Let's now
|
|
|
|
|
build a simple app server that uses this client to retrieve documents. This
|
|
|
|
|
is somewhat contrived, but hopefully it illustrates the typical three-tier
|
|
|
|
|
application architecture.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
One note: we're also going to take advantage of `lens-aeson` here, which may
|
2018-10-12 17:48:25 +02:00
|
|
|
|
look a bit foreign. The gist of it is that we're going to traverse a JSON
|
2018-10-12 05:51:30 +02:00
|
|
|
|
`Value` from Elasticsearch and try to extract some kind of document to
|
|
|
|
|
return.
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
Imagine, then, that this is our real server implementation:
|
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```haskell
|
2018-10-12 17:48:25 +02:00
|
|
|
|
type DocApi =
|
2018-10-12 05:51:30 +02:00
|
|
|
|
"docs" :> Capture "docId" Integer :> Get '[JSON] Value
|
|
|
|
|
|
2018-10-14 22:27:33 +02:00
|
|
|
|
docsApp :: Text -> Text -> Application
|
|
|
|
|
docsApp esHost esPort = serve (Proxy :: Proxy DocApi) $ docServer esHost esPort
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
docServer :: Text -> Text -> Server DocApi
|
2018-10-12 05:51:30 +02:00
|
|
|
|
docServer esHost esPort = getDocById esHost esPort
|
|
|
|
|
|
|
|
|
|
-- Our Handler tries to get a doc from Elasticsearch and then tries to parse
|
|
|
|
|
-- it. Unfortunately, there's a lot of opportunity for failure in these
|
|
|
|
|
-- actions
|
|
|
|
|
getDocById :: Text -> Text -> Integer -> Handler Value
|
|
|
|
|
getDocById esHost esPort docId = do
|
2019-02-18 19:17:46 +01:00
|
|
|
|
-- Our Servant Client function returns Either ClientError Value here:
|
2018-10-12 05:51:30 +02:00
|
|
|
|
docRes <- liftIO $ runSearchClient esHost esPort (getDocument docId)
|
|
|
|
|
case docRes of
|
|
|
|
|
Left err -> throwError $ err404 { errBody = "Failed looking up content" }
|
|
|
|
|
Right value -> do
|
|
|
|
|
-- we'll either fail to parse our document or we'll return it
|
|
|
|
|
case value ^? _Object . ix "_source" of
|
|
|
|
|
Nothing -> throwError $ err400 { errBody = "Failed parsing content" }
|
|
|
|
|
Just obj -> pure obj
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
### Testing Our Backend
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
So the above represents our application and is close to a server we may
|
2018-10-13 02:32:20 +02:00
|
|
|
|
actually deploy. How then shall we test this application?
|
2018-10-12 17:48:25 +02:00
|
|
|
|
|
|
|
|
|
Ideally, we'd like it to make requests of a *real* Elasticsearch server, but
|
|
|
|
|
we certainly don't want our tests to trigger requests to a live, production
|
2018-10-12 05:51:30 +02:00
|
|
|
|
database. In addition, we don't want to depend on our real Elasticsearch
|
|
|
|
|
server having specific, consistent results for us to test against, because
|
|
|
|
|
that would make our tests flaky (and flaky tests are sometimes described as
|
|
|
|
|
worse than not having tests at all).
|
|
|
|
|
|
|
|
|
|
One solution to this is to create a trivial Elasticsearch server as part of
|
|
|
|
|
our testing code. We can do this relatively easily because we already have
|
|
|
|
|
an API definition for it above. With a *real* server, we can then let our own
|
|
|
|
|
application make requests of it and we'll simulate different scenarios in
|
|
|
|
|
order to make sure our application responds the way we expect it to.
|
|
|
|
|
|
|
|
|
|
Let's start with some helpers which will allow us to run a testing version
|
|
|
|
|
of our Elasticsearch server in another thread:
|
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
-- | We'll run the Elasticsearch server so we can test behaviors
|
|
|
|
|
withElasticsearch :: IO () -> IO ()
|
|
|
|
|
withElasticsearch action =
|
|
|
|
|
bracket (liftIO $ C.forkIO $ Warp.run 9999 esTestApp)
|
|
|
|
|
C.killThread
|
|
|
|
|
(const action)
|
|
|
|
|
|
|
|
|
|
esTestApp :: Application
|
|
|
|
|
esTestApp = serve (Proxy :: Proxy SearchAPI) esTestServer
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
esTestServer :: Server SearchAPI
|
2018-10-12 05:51:30 +02:00
|
|
|
|
esTestServer = getESDocument
|
|
|
|
|
|
2018-10-13 15:35:56 +02:00
|
|
|
|
-- This is the *mock* handler we're going to use. We create it
|
|
|
|
|
-- here specifically to trigger different behavior in our tests.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
getESDocument :: Integer -> Handler Value
|
|
|
|
|
getESDocument docId
|
2018-10-14 19:19:49 +02:00
|
|
|
|
-- arbitrary things we can use in our tests to simulate failure:
|
|
|
|
|
-- we want to trigger different code paths.
|
2018-10-12 17:48:25 +02:00
|
|
|
|
| docId > 1000 = throwError err500
|
2018-10-12 05:51:30 +02:00
|
|
|
|
| docId > 500 = pure . Object $ HM.fromList [("bad", String "data")]
|
2018-10-12 17:48:25 +02:00
|
|
|
|
| otherwise = pure $ Object $ HM.fromList [("_source", Object $ HM.fromList [("a", String "b")])]
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
Now, we should be ready to write some tests.
|
|
|
|
|
|
|
|
|
|
In this case, we're going to use `hspec-wai`, which will give us a simple way
|
|
|
|
|
to run our application, make requests, and make assertions against the
|
|
|
|
|
responses we receive.
|
|
|
|
|
|
|
|
|
|
Hopefully, this will simplify our testing code:
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
thirdPartyResourcesSpec :: Spec
|
|
|
|
|
thirdPartyResourcesSpec = around_ withElasticsearch $ do
|
2018-10-14 19:19:49 +02:00
|
|
|
|
-- we call `with` from `hspec-wai` and pass *real* `Application`
|
2018-10-14 22:27:33 +02:00
|
|
|
|
with (pure $ docsApp "localhost" "9999") $ do
|
2018-10-12 05:51:30 +02:00
|
|
|
|
describe "GET /docs" $ do
|
|
|
|
|
it "should be able to get a document" $
|
2018-10-12 17:48:25 +02:00
|
|
|
|
-- `get` is a function from hspec-wai`.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
get "/docs/1" `shouldRespondWith` 200
|
|
|
|
|
it "should be able to handle connection failures" $
|
|
|
|
|
get "/docs/1001" `shouldRespondWith` 404
|
|
|
|
|
it "should be able to handle parsing failures" $
|
|
|
|
|
get "/docs/501" `shouldRespondWith` 400
|
|
|
|
|
it "should be able to handle odd HTTP requests" $
|
|
|
|
|
-- we can also make all kinds of arbitrary custom requests to see how
|
|
|
|
|
-- our server responds using the `request` function:
|
2018-10-12 17:48:25 +02:00
|
|
|
|
-- request :: Method -> ByteString -> [Header]
|
2018-10-12 05:51:30 +02:00
|
|
|
|
-- -> LB.ByteString -> WaiSession SResponse
|
2018-10-12 17:48:25 +02:00
|
|
|
|
request methodPost "/docs/501" [] "{" `shouldRespondWith` 405
|
|
|
|
|
it "we can also do more with the Response using hspec-wai's matchers" $
|
|
|
|
|
-- see also `MatchHeader` and JSON-matching tools as well...
|
|
|
|
|
get "/docs/1" `shouldRespondWith` 200 { matchBody = MatchBody bodyMatcher }
|
|
|
|
|
|
|
|
|
|
bodyMatcher :: [Network.HTTP.Types.Header] -> Body -> Maybe String
|
|
|
|
|
bodyMatcher _ body = case (decode body :: Maybe Value) of
|
|
|
|
|
-- success in this case means we return `Nothing`
|
|
|
|
|
Just val | val == (Object $ HM.fromList [("a", String "b")]) -> Nothing
|
|
|
|
|
_ -> Just "This is how we represent failure: this message will be printed"
|
2018-10-12 05:51:30 +02:00
|
|
|
|
```
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
Out of the box, `hspec-wai` provides a lot of useful tools for us to run tests
|
|
|
|
|
against our application. What happens when we run these tests?
|
2018-10-12 17:48:25 +02:00
|
|
|
|
|
|
|
|
|
```
|
|
|
|
|
$ cabal new-test all
|
|
|
|
|
...
|
|
|
|
|
|
|
|
|
|
GET /docs
|
|
|
|
|
should be able to get a document
|
|
|
|
|
should be able to handle connection failures
|
|
|
|
|
should be able to handle parsing failures
|
|
|
|
|
should be able to handle odd HTTP requests
|
|
|
|
|
we can also do more with the Response using hspec-wai's matchers
|
|
|
|
|
```
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
Fortunately, they all passed! Let's move to another strategy: whole-API
|
|
|
|
|
testing.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
## Servant Quickcheck
|
|
|
|
|
|
|
|
|
|
[`servant-quickcheck`](https://github.com/haskell-servant/servant-quickcheck)
|
|
|
|
|
is a project that allows users to write tests for whole Servant APIs using
|
|
|
|
|
quickcheck-style property-checking mechanisms.
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
`servant-quickcheck` is great for asserting API-wide rules, such as "no
|
2018-10-12 05:51:30 +02:00
|
|
|
|
endpoint throws a 500" or "all 301 status codes also come with a Location
|
|
|
|
|
header". The project even comes with a number of predicates that reference
|
|
|
|
|
the [RFCs they originate from](https://github.com/haskell-servant/servant-quickcheck/blob/master/src/Servant/QuickCheck/Internal/Predicates.hs).
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
In other words, it's one way to assert that your APIs conform to specs and
|
|
|
|
|
best practices.
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
### Quickcheckable API
|
|
|
|
|
|
|
|
|
|
Let's make an API and a server to demonstrate how to use `servant-quickcheck`:
|
|
|
|
|
|
|
|
|
|
```haskell
|
|
|
|
|
type API = ReqBody '[JSON] String :> Post '[JSON] String
|
|
|
|
|
:<|> Get '[JSON] Int
|
|
|
|
|
:<|> BasicAuth "some-realm" () :> Get '[JSON] ()
|
|
|
|
|
|
|
|
|
|
api :: Proxy API
|
|
|
|
|
api = Proxy
|
|
|
|
|
|
|
|
|
|
server :: IO (Server API)
|
|
|
|
|
server = do
|
|
|
|
|
mvar <- newMVar ""
|
|
|
|
|
return $ (\x -> liftIO $ swapMVar mvar x)
|
2018-10-25 22:16:16 +02:00
|
|
|
|
:<|> (liftIO $ readMVar mvar >>= return . length)
|
2018-10-12 05:51:30 +02:00
|
|
|
|
:<|> (const $ return ())
|
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
### Using `servant-quickcheck`
|
|
|
|
|
|
2018-10-12 17:48:25 +02:00
|
|
|
|
Let's build some tests for our API using `servant-quickcheck`.
|
|
|
|
|
|
|
|
|
|
Similar to the above examples, we're going to create `Spec`s, but in this
|
|
|
|
|
case, we'll rely on a number of predicates available from `servant-quickcheck`
|
|
|
|
|
to see if our API server conforms to best practices:
|
2018-10-12 05:51:30 +02:00
|
|
|
|
|
|
|
|
|
```haskell
|
2018-10-12 17:48:25 +02:00
|
|
|
|
-- Let's set some QuickCheck values
|
|
|
|
|
args :: Args
|
|
|
|
|
args = defaultArgs { maxSuccess = 500 }
|
|
|
|
|
|
|
|
|
|
-- Here's a Servant Context object we'll use
|
|
|
|
|
ctx :: Context '[BasicAuthCheck ()]
|
|
|
|
|
ctx = BasicAuthCheck (const . return $ NoSuchUser) :. EmptyContext
|
|
|
|
|
|
|
|
|
|
|
2018-10-12 05:51:30 +02:00
|
|
|
|
servantQuickcheckSpec :: Spec
|
|
|
|
|
servantQuickcheckSpec = describe "" $ do
|
|
|
|
|
it "API demonstrates best practices" $
|
2018-10-12 17:48:25 +02:00
|
|
|
|
-- `withServerServer` and `withServantServerAndContext` come from `servant-quickcheck`
|
|
|
|
|
withServantServerAndContext api ctx server $ \burl ->
|
|
|
|
|
-- `serverSatisfies` and the predicates also come from `servant-quickcheck`
|
2018-10-12 05:51:30 +02:00
|
|
|
|
serverSatisfies api burl args (unauthorizedContainsWWWAuthenticate
|
|
|
|
|
<%> not500
|
2018-10-13 02:32:20 +02:00
|
|
|
|
<%> onlyJsonObjects -- this one isn't true!
|
2018-10-12 05:51:30 +02:00
|
|
|
|
<%> mempty)
|
|
|
|
|
|
|
|
|
|
it "API doesn't have these things implemented yet" $
|
2018-10-12 17:48:25 +02:00
|
|
|
|
withServantServerAndContext api ctx server $ \burl -> do
|
2018-10-12 05:51:30 +02:00
|
|
|
|
serverDoesntSatisfy api burl args (getsHaveCacheControlHeader
|
|
|
|
|
<%> notAllowedContainsAllowHeader
|
|
|
|
|
<%> mempty)
|
2018-10-12 17:48:25 +02:00
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
Let's see what happens when we run these tests:
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
```
|
|
|
|
|
API demonstrates best practices FAILED [2]
|
|
|
|
|
+++ OK, passed 500 tests.
|
|
|
|
|
API doesn't have these things implemented yet
|
|
|
|
|
|
|
|
|
|
src/Servant/QuickCheck/Internal/QuickCheck.hs:143:11:
|
|
|
|
|
2) Main[339:25] API demonstrates best practices
|
|
|
|
|
Failed:
|
|
|
|
|
Just Predicate failed
|
|
|
|
|
Predicate: onlyJsonObjects
|
|
|
|
|
|
|
|
|
|
Response:
|
|
|
|
|
Status code: 200
|
|
|
|
|
Headers: "Transfer-Encoding": "chunked"
|
|
|
|
|
"Date": "Fri, 12 Oct 2018 04:36:22 GMT"
|
|
|
|
|
"Server": "Warp/3.2.25"
|
|
|
|
|
"Content-Type": "application/json;charset=utf-8"
|
|
|
|
|
Body: ""
|
|
|
|
|
|
|
|
|
|
To rerun use: --match "/Main[339:25]/API demonstrates best practices/"
|
|
|
|
|
|
|
|
|
|
Randomized with seed 1046277487
|
|
|
|
|
|
|
|
|
|
Finished in 0.4306 seconds
|
|
|
|
|
```
|
|
|
|
|
|
2018-10-13 02:32:20 +02:00
|
|
|
|
Hmm. It looks like we *thought* our API only returned JSON objects, which is a
|
2018-10-12 17:48:25 +02:00
|
|
|
|
best practice, but in fact, we *did* have an endpoint that returned an empty
|
|
|
|
|
body, which you can see in the printed response above: `Body: ""`. We should
|
|
|
|
|
consider revising our API to only return top-level JSON Objects in the future!
|
|
|
|
|
|
|
|
|
|
### Other Cool Things
|
|
|
|
|
|
|
|
|
|
`servant-quickcheck` also has a cool mechanism where you can compare two API
|
|
|
|
|
servers to demonstrate that they respond identically to requests. This may be
|
|
|
|
|
useful if you are planning to rewrite one API in another language or with
|
|
|
|
|
another web framework. You have to specify whether you're looking for
|
|
|
|
|
`jsonEquality` vs regular `ByteString` equality, though.
|
|
|
|
|
|
|
|
|
|
## Conclusion
|
|
|
|
|
|
|
|
|
|
There are lots of techniques for testing and we only covered a few here.
|
|
|
|
|
|
2018-10-14 19:19:49 +02:00
|
|
|
|
Useful libraries such as `hspec-wai` have ways of running Wai `Application`s
|
2018-10-12 17:48:25 +02:00
|
|
|
|
and sending requests to them, while Servant's type-level DSL for defining APIs
|
2018-10-14 19:19:49 +02:00
|
|
|
|
allows us to more easily mock out servers and to derive clients, which will
|
|
|
|
|
only craft valid requests.
|
|
|
|
|
|
|
|
|
|
Lastly, if you want a broad overview of where your application fits in with
|
|
|
|
|
regard to best practices, consider using `servant-quickcheck`.
|
|
|
|
|
|
|
|
|
|
This program is available as a cabal project
|
2018-10-25 22:16:16 +02:00
|
|
|
|
[here](https://github.com/haskell-servant/servant/tree/master/doc/cookbook/testing).
|