servant/doc/cookbook/using-free-client/UsingFreeClient.lhs
2018-07-06 00:21:17 +03:00

174 lines
4.8 KiB
Plaintext

# Using Free Client (for tests)
Someone asked on IRC about getting `Request` & `Response` of what
`servant-client` uses, for testing purposes. My response: to ad-hoc extend
`servant-client` (as for tests), use `Servant.Client.Free`. This recipe is an
evidence.
First the module header, but this time We'll comment the imports.
```haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Main (main) where
```
We will primarily use `Servant.Client.Free`, it doesn't re-export anything
from `free` package, so we need to import it as well.
```haskell
import Control.Monad.Free
import Servant.Client.Free
```
Also we'll use `servant-client` internals, which uses `http-client`,
so let's import them *qualified*
```haskell
import qualified Servant.Client.Internal.HttpClient as I
import qualified Network.HTTP.Client as HTTP
```
The rest of the imports are for a server we implement here for completeness.
```haskell
import Servant
import Network.Wai.Handler.Warp (run)
import System.Environment (getArgs)
```
## API & Main
We'll work with a very simple API:
```haskell
type API = "square" :> Capture "n" Int :> Get '[JSON] Int
api :: Proxy API
api = Proxy
```
Next we implement a `main`. If passed `server` it will run `server`, if
`client` a small `test` (to be defined next) will be run. This should be pretty
straigh-forward:
```haskell
main :: IO ()
main = do
args <- getArgs
case args of
("server":_) -> do
putStrLn "Starting cookbook-using-free-client at http://localhost:8000"
run 8000 $ serve api $ \n -> return (n * n)
("client":_) ->
test
_ -> do
putStrLn "Try:"
putStrLn "cabal new-run cookbook-using-free-client server"
putStrLn "cabal new-run cookbook-using-free-client client"
```
## Test
In the actual test, we'll use a `Servant.Client.Free` client.
Cecause we have a single endpoint API, we'll get a single client function:
```haskell
fcli :: Int -> Free ClientF Int
fcli = client api
```
Next, we can write our small test. We'll pass a value to `fcli` and inspect
the `Free` structure. First three possibilities are self-explanatory:
```haskell
test :: IO ()
test = case fcli 42 of
Pure n ->
putStrLn $ "ERROR: got pure result: " ++ show n
Free (Throw err) ->
putStrLn $ "ERROR: got error right away: " ++ show err
Free (StreamingRequest _req _k) ->
putStrLn $ "ERROR: need to do streaming request" -- TODO: no Show Req :(
```
We are interested in `RunRequest`, that's what client should block on:
```haskell
Free (RunRequest req k) -> do
```
Then we need to prepare the context, get HTTP (connection) `Manager`
and `BaseUrl`:
```haskell
burl <- parseBaseUrl "http://localhost:8000"
mgr <- HTTP.newManager HTTP.defaultManagerSettings
```
Now we can use `servant-client` internals to convert servant's `Request`
to http-client's `Request`, and we can inspect it:
```haskell
let req' = I.requestToClientRequest burl req
putStrLn $ "Making request: " ++ show req'
```
`servant-client` does a bit more than `httpLbs`, but that's enough for us.
We get back a http-client `Response` which we can also inspect
```haskell
res' <- HTTP.httpLbs req' mgr
putStrLn $ "Got response: " ++ show res'
```
And we continue by turning http-client's `Response` into servant's `Response`,
and calling the continuation. We should get a `Pure` value.
```haskell
let res = I.clientResponseToResponse res'
case k res of
Pure n ->
putStrLn $ "Expected 1764, got " ++ show n
_ ->
putStrLn "ERROR: didn't got a response"
```
So that's it. Using `Free` we can evaluate servant clients step-by-step, and
validate that they or the backend does what we expect (think: debugger). At the
end an example of client run (prettified):
```
Making request: Request {
host = "localhost"
port = 8000
secure = False
requestHeaders = [("Accept","application/json;charset=utf-8,application/json")]
path = "/square/42"
queryString = ""
method = "GET"
proxy = Nothing
rawBody = False
redirectCount = 10
responseTimeout = ResponseTimeoutDefault
requestVersion = HTTP/1.1
}
Got response: Response
{ responseStatus = Status {statusCode = 200, statusMessage = "OK"}
, responseVersion = HTTP/1.1
, responseHeaders =
[ ("Transfer-Encoding","chunked")
, ("Date","Thu, 05 Jul 2018 21:12:41 GMT")
, ("Server","Warp/3.2.22")
, ("Content-Type","application/json;charset=utf-8")
]
, responseBody = "1764"
, responseCookieJar = CJ {expose = []}
, responseClose' = ResponseClose
}
Expected 1764, got 1764
```