servant-openapi3-2.0.0.1: Generate a Swagger/OpenAPI/OAS 3.0 specification for your servant API.

LicenseBSD3
MaintainerNickolay Kudasov <nickolay@getshoptv.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Servant.OpenApi

Contents

Description

This module provides means to generate and manipulate OpenApi specification for servant APIs.

OpenApi is a project used to describe and document RESTful APIs.

The OpenApi specification defines a set of files required to describe such an API. These files can then be used by the OpenApi-UI project to display the API and OpenApi-Codegen to generate clients in various languages. Additional utilities can also take advantage of the resulting files, such as testing tools.

For more information see OpenApi documentation.

Synopsis

How to use this library

This section explains how to use this library to generate OpenApi specification, modify it and run automatic tests for a servant API.

For the purposes of this section we will use this servant API:

>>> data User = User { name :: String, age :: Int } deriving (Show, Generic, Typeable)
>>> newtype UserId = UserId Integer deriving (Show, Generic, Typeable, ToJSON)
>>> instance ToJSON User
>>> instance ToSchema User
>>> instance ToSchema UserId
>>> instance ToParamSchema UserId
>>> type GetUsers = Get '[JSON] [User]
>>> type GetUser  = Capture "user_id" UserId :> Get '[JSON] User
>>> type PostUser = ReqBody '[JSON] User :> Post '[JSON] UserId
>>> type UserAPI  = GetUsers :<|> GetUser :<|> PostUser

Here we define a user API with three endpoints. GetUsers endpoint returns a list of all users. GetUser returns a user given his/her ID. PostUser creates a new user and returns his/her ID.

Generate OpenApi

In order to generate OpenApi specification for a servant API, just use toOpenApi:

>>> BSL8.putStrLn $ encode $ toOpenApi (Proxy :: Proxy UserAPI)
{"openapi":"3.0.0","info":{"version":"","title":""},"paths":{"/":{"get":{"responses":{"200":{"content":{"application/json;charset=utf-8":{"schema":{"items":{"$ref":"#/components/schemas/User"},"type":"array"}}},"description":""}}},"post":{"requestBody":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}}},"responses":{"400":{"description":"Invalid `body`"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/UserId"}}},"description":""}}}},"/{user_id}":{"get":{"parameters":[{"required":true,"schema":{"type":"integer"},"in":"path","name":"user_id"}],"responses":{"404":{"description":"`user_id` not found"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}},"description":""}}}}},"components":{"schemas":{"User":{"required":["name","age"],"type":"object","properties":{"age":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"name":{"type":"string"}}},"UserId":{"type":"integer"}}}}

By default toOpenApi will generate specification for all API routes, parameters, headers, responses and data schemas.

For some parameters it will also add 400 and/or 404 responses with a description mentioning parameter name.

Data schemas come from ToParamSchema and ToSchema classes.

Annotate

While initially generated OpenApi looks good, it lacks some information it can't get from a servant API.

We can add this information using field lenses from Data.OpenApi:

>>> :{
BSL8.putStrLn $ encode $ toOpenApi (Proxy :: Proxy UserAPI)
  & info.title        .~ "User API"
  & info.version      .~ "1.0"
  & info.description  ?~ "This is an API for the Users service"
  & info.license      ?~ "MIT"
  & servers           .~ ["https://example.com"]
:}
{"openapi":"3.0.0","info":{"version":"1.0","title":"User API","license":{"name":"MIT"},"description":"This is an API for the Users service"},"servers":[{"url":"https://example.com"}],"paths":{"/":{"get":{"responses":{"200":{"content":{"application/json;charset=utf-8":{"schema":{"items":{"$ref":"#/components/schemas/User"},"type":"array"}}},"description":""}}},"post":{"requestBody":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}}},"responses":{"400":{"description":"Invalid `body`"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/UserId"}}},"description":""}}}},"/{user_id}":{"get":{"parameters":[{"required":true,"schema":{"type":"integer"},"in":"path","name":"user_id"}],"responses":{"404":{"description":"`user_id` not found"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}},"description":""}}}}},"components":{"schemas":{"User":{"required":["name","age"],"type":"object","properties":{"age":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"name":{"type":"string"}}},"UserId":{"type":"integer"}}}}

It is also useful to annotate or modify certain endpoints. subOperations provides a convenient way to zoom into a part of an API.

subOperations sub api traverses all operations of the api which are also present in sub. Furthermore, sub is required to be an exact sub API of @api. Otherwise it will not typecheck.

Data.OpenApi.Operation provides some useful helpers that can be used with subOperations. One example is applying tags to certain endpoints:

>>> let getOps  = subOperations (Proxy :: Proxy (GetUsers :<|> GetUser)) (Proxy :: Proxy UserAPI)
>>> let postOps = subOperations (Proxy :: Proxy PostUser) (Proxy :: Proxy UserAPI)
>>> :{
BSL8.putStrLn $ encode $ toOpenApi (Proxy :: Proxy UserAPI)
  & applyTagsFor getOps  ["get"  & description ?~ "GET operations"]
  & applyTagsFor postOps ["post" & description ?~ "POST operations"]
:}
{"openapi":"3.0.0","info":{"version":"","title":""},"paths":{"/":{"get":{"tags":["get"],"responses":{"200":{"content":{"application/json;charset=utf-8":{"schema":{"items":{"$ref":"#/components/schemas/User"},"type":"array"}}},"description":""}}},"post":{"tags":["post"],"requestBody":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}}},"responses":{"400":{"description":"Invalid `body`"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/UserId"}}},"description":""}}}},"/{user_id}":{"get":{"tags":["get"],"parameters":[{"required":true,"schema":{"type":"integer"},"in":"path","name":"user_id"}],"responses":{"404":{"description":"`user_id` not found"},"200":{"content":{"application/json;charset=utf-8":{"schema":{"$ref":"#/components/schemas/User"}}},"description":""}}}}},"components":{"schemas":{"User":{"required":["name","age"],"type":"object","properties":{"age":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"name":{"type":"string"}}},"UserId":{"type":"integer"}}},"tags":[{"name":"get","description":"GET operations"},{"name":"post","description":"POST operations"}]}

This applies "get" tag to the GET endpoints and "post" tag to the POST endpoint of the User API.

Test

Automatic generation of data schemas uses ToSchema instances for the types used in a servant API. But to encode/decode actual data servant uses different classes. For instance in UserAPI User is always encoded/decoded using ToJSON and FromJSON instances.

To be sure your Haskell server/client handles data properly you need to check that ToJSON instance always generates values that satisfy schema produced by ToSchema instance.

With validateEveryToJSON it is possible to test all those instances automatically, without having to write down every type:

>>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
>>> instance Arbitrary UserId where arbitrary = UserId <$> arbitrary
>>> hspec $ validateEveryToJSON (Proxy :: Proxy UserAPI)

[User]
...
User
...
UserId
...
Finished in ... seconds
3 examples, 0 failures

Although servant is great, chances are that your API clients don't use Haskell. In many cases swagger.json serves as a specification, not a Haskell type.

In this cases it is a good idea to store generated and annotated OpenApi in a swagger.json file under a version control system (such as Git, Subversion, Mercurial, etc.).

It is also recommended to version API based on changes to the swagger.json rather than changes to the Haskell API.

See TodoSpec.hs for an example of a complete test suite for a swagger specification.

Serve

If you're implementing a server for an API, you might also want to serve its OpenApi specification.

See Todo.hs for an example of a server.

HasOpenApi class

class HasOpenApi api where Source #

Generate a OpenApi specification for a servant API.

To generate OpenApi specification, your data types need ToParamSchema and/or ToSchema instances.

ToParamSchema is used for Capture, QueryParam and Header. ToSchema is used for ReqBody and response data types.

You can easily derive those instances via Generic. For more information, refer to openapi3 documentation.

Example:

newtype Username = Username String deriving (Generic, ToText)

instance ToParamSchema Username

data User = User
  { username :: Username
  , fullname :: String
  } deriving (Generic)

instance ToJSON User
instance ToSchema User

type MyAPI = QueryParam "username" Username :> Get '[JSON] User

myOpenApi :: OpenApi
myOpenApi = toOpenApi (Proxy :: Proxy MyAPI)

Methods

toOpenApi :: Proxy api -> OpenApi Source #

Generate a OpenApi specification for a servant API.

Instances
HasOpenApi Raw Source # 
Instance details

Defined in Servant.OpenApi.Internal

HasOpenApi EmptyAPI Source # 
Instance details

Defined in Servant.OpenApi.Internal

OpenApiMethod method => HasOpenApi (NoContentVerb method :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

(HasOpenApi a, HasOpenApi b) => HasOpenApi (a :<|> b :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (a :<|> b) -> OpenApi Source #

HasOpenApi sub => HasOpenApi (WithNamedContext x c sub :: Type) Source #

WithNamedContext combinator does not change our specification at all.

Instance details

Defined in Servant.OpenApi.Internal

HasOpenApi sub => HasOpenApi (HttpVersion :> sub :: Type) Source #

HttpVersion combinator does not change our specification at all.

Instance details

Defined in Servant.OpenApi.Internal

(ToSchema a, Accept ct, HasOpenApi sub, KnownSymbol (FoldDescription mods)) => HasOpenApi (StreamBody' mods fr ct a :> sub :: Type) Source #

This instance is an approximation.

Since: 1.1.7

Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (StreamBody' mods fr ct a :> sub) -> OpenApi Source #

(ToSchema a, AllAccept cs, HasOpenApi sub, KnownSymbol (FoldDescription mods)) => HasOpenApi (ReqBody' mods cs a :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (ReqBody' mods cs a :> sub) -> OpenApi Source #

HasOpenApi sub => HasOpenApi (RemoteHost :> sub :: Type) Source #

RemoteHost combinator does not change our specification at all.

Instance details

Defined in Servant.OpenApi.Internal

(KnownSymbol sym, ToParamSchema a, HasOpenApi sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasOpenApi (QueryParam' mods sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (QueryParam' mods sym a :> sub) -> OpenApi Source #

(KnownSymbol sym, ToParamSchema a, HasOpenApi sub) => HasOpenApi (QueryParams sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (QueryParams sym a :> sub) -> OpenApi Source #

(KnownSymbol sym, HasOpenApi sub) => HasOpenApi (QueryFlag sym :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (QueryFlag sym :> sub) -> OpenApi Source #

(KnownSymbol sym, ToParamSchema a, HasOpenApi sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasOpenApi (Header' mods sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Header' mods sym a :> sub) -> OpenApi Source #

HasOpenApi sub => HasOpenApi (IsSecure :> sub :: Type) Source #

IsSecure combinator does not change our specification at all.

Instance details

Defined in Servant.OpenApi.Internal

(KnownSymbol desc, HasOpenApi api) => HasOpenApi (Summary desc :> api :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Summary desc :> api) -> OpenApi Source #

(KnownSymbol desc, HasOpenApi api) => HasOpenApi (Description desc :> api :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Description desc :> api) -> OpenApi Source #

(KnownSymbol sym, ToParamSchema a, HasOpenApi sub, KnownSymbol (FoldDescription mods)) => HasOpenApi (Capture' mods sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Capture' mods sym a :> sub) -> OpenApi Source #

(KnownSymbol sym, ToParamSchema a, HasOpenApi sub) => HasOpenApi (CaptureAll sym a :> sub :: Type) Source #

OpenApi Spec doesn't have a notion of CaptureAll, this instance is the best effort.

Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (CaptureAll sym a :> sub) -> OpenApi Source #

HasOpenApi sub => HasOpenApi (Vault :> sub :: Type) Source #

Vault combinator does not change our specification at all.

Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Vault :> sub) -> OpenApi Source #

(KnownSymbol sym, HasOpenApi sub) => HasOpenApi (sym :> sub :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (sym :> sub) -> OpenApi Source #

(AllAccept cs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs NoContent :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Verb method status cs NoContent) -> OpenApi Source #

(ToSchema a, AllAccept cs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs a :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Verb method status cs a) -> OpenApi Source #

(AllAccept cs, AllToResponseHeader hs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs (Headers hs NoContent) :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Verb method status cs (Headers hs NoContent)) -> OpenApi Source #

(ToSchema a, AllAccept cs, AllToResponseHeader hs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs (Headers hs a) :: Type) Source # 
Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Verb method status cs (Headers hs a)) -> OpenApi Source #

(ToSchema a, Accept ct, KnownNat status, OpenApiMethod method) => HasOpenApi (Stream method status fr ct a :: Type) Source #

Since: 1.1.7

Instance details

Defined in Servant.OpenApi.Internal

Methods

toOpenApi :: Proxy (Stream method status fr ct a) -> OpenApi Source #

Manipulation

subOperations Source #

Arguments

:: (IsSubAPI sub api, HasOpenApi sub) 
=> Proxy sub

Part of a servant API.

-> Proxy api

The whole servant API.

-> Traversal' OpenApi Operation 

All operations of sub API. This is similar to operationsOf but ensures that operations indeed belong to the API at compile time.

Testing

validateEveryToJSON Source #

Arguments

:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) 
=> proxy api

Servant API.

-> Spec 

Verify that every type used with JSON content type in a servant API has compatible ToJSON and ToSchema instances using validateToJSON.

NOTE: validateEveryToJSON does not perform string pattern validation. See validateEveryToJSONWithPatternChecker.

validateEveryToJSON will produce one prop specification for every type in the API. Each type only gets one test, even if it occurs multiple times in the API.

>>> data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
>>> newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
>>> instance ToJSON User
>>> instance ToSchema User
>>> instance ToSchema UserId
>>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
>>> type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
>>> hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)

ToJSON matches ToSchema
  User
...
  UserId
...
Finished in ... seconds
2 examples, 0 failures

For the test to compile all body types should have the following instances:

If any of the instances is missing, you'll get a descriptive type error:

>>> data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
>>> instance ToJSON Contact
>>> instance ToSchema Contact
>>> type ContactAPI = Get '[JSON] Contact
>>> hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
...
...No instance for (Arbitrary Contact)
...  arising from a use of ‘validateEveryToJSON’
...

validateEveryToJSONWithPatternChecker Source #

Arguments

:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) 
=> (Pattern -> Text -> Bool)

Pattern checker.

-> proxy api

Servant API.

-> Spec 

Verify that every type used with JSON content type in a servant API has compatible ToJSON and ToSchema instances using validateToJSONWithPatternChecker.

For validation without patterns see validateEveryToJSON.