servant-benchmark: Generate benchamrk files from a Servant API

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Please see the README on GitHub at https://github.com/3kyro/servant-benchmark#README


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.1.2.0, 0.2.0.0
Change log ChangeLog.md
Dependencies aeson, base (>=4.7 && <5), base64-bytestring, bytestring, case-insensitive, http-media, http-types, QuickCheck, servant, text, yaml [details]
License BSD-3-Clause
Copyright 2021 Kyriakos Papachrysanthou
Author Kyriakos Papachrysanthou
Maintainer papachrysanthou.k@gmaim.com
Category Web
Home page https://github.com/3kyro/servant-benchmark#readme
Bug tracker https://github.com/3kyro/servant-benchmark/issues
Source repo head: git clone https://github.com/3kyro/servant-benchmark
Uploaded by 3kyro at 2021-04-26T07:52:41Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for servant-benchmark-0.1.0.0

[back to package description]

servant-benchmark

A library for producing random request data from Servant APIs.

Building a Generator

The Generator type must closely follow the structure of the Servant API.

As an example, the following is a valid Generator for a contrived servant API

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}

type API = 
    "books" :> Get '[JSON] [Book]
    :<|> "view-my-referer" :> Header "from" Referer :> Get '[JSON] Referer
    :<|> "users" :> Capture "userId" Integer :> ReqBody '[JSON] User :> Put '[JSON] User
    :<|> "post" :> QueryParam "segments" Text :> Get '[JSON] Post
    :<|> Raw

generator :: Generator API
let generator =
    ("books", 1)
    :|: arbitrary :>: ("referer", 2)
    :|: pure 1001 :>: arbitrary :>: ("users endpoint", 2)
    :|: elements ["title", "contents", "post"] :>: ("post", 4)
    :|: ("raw", 0)

The first endpoint "books" does not require request data and so only the name / weight tuple is provided.

The "view-my-referer" endpoint requires a "from" header with an accompanying Referer value. Here we assume Referer has an Arbitrary instance to provide a random value. The endpoint generator finishes with the name/weight indication.

The "users" endpoint requires two different request values. An Integer capture representing a user id as well as a User value. We hard-code the user id to 1001 using the monadic pure and assume that User has an Arbitrary instance to produce a random value. We finish with the endpoint's name/weight as necessary.

The "post" endpoint requires a Text query parameter. We provide a fixed set of possible values using the elements function from the QuickCheck package. With a weight of 4, four instances of the "post" endpoint will be produced, each with a random value from the specified set.

Finally our API provides a Raw endpoint for serving static files, but we'd rather not benchmark it. Providing a 0 weight ensures that no request will be generated

Basic Auth

A generator for an endpoint using a BasicAuth combinator requires both a function to convert the requested user data type to BasicAuthData as well as a Gen value for the requested user data.

example:

type privateAPI = "private" :> BasicAuth "foo-realm" User :> PrivateAPI

toBasicAuthData :: User -> BasicAuthData
toBasicAuthData user = ... 

-- assuming `User` has an `Arbitrary` instance
let generator = toBasicAuthData :>: arbitrary :>: ("basicAuth", 1)

The information will be encoded as an Authorization header.

Supported tools

The following benchmarking tools are supported :

If you'd like your favorite tool to be supported, don't hesitate to tell me so in an issue, or better yet submit a PR.

Next steps