servant-swagger-1.1.8: Generate a Swagger/OpenAPI/OAS 2.0 specification for your servant API.

Safe HaskellNone
LanguageHaskell2010

Servant.Swagger.Internal

Synopsis

Documentation

class HasSwagger api where Source #

Generate a Swagger specification for a servant API.

To generate Swagger 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 swagger2 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

mySwagger :: Swagger
mySwagger = toSwagger (Proxy :: Proxy MyAPI)

Methods

toSwagger :: Proxy api -> Swagger Source #

Generate a Swagger specification for a servant API.

Instances
HasSwagger Raw Source # 
Instance details

Defined in Servant.Swagger.Internal

HasSwagger EmptyAPI Source # 
Instance details

Defined in Servant.Swagger.Internal

SwaggerMethod method => HasSwagger (NoContentVerb method :: Type) Source # 
Instance details

Defined in Servant.Swagger.Internal

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (a :<|> b) -> Swagger Source #

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

WithNamedContext combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

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

HttpVersion combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

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

This instance is an approximation.

Since: 1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (StreamBody' mods fr ct a :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (ReqBody' mods cs a :> sub) -> Swagger Source #

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

RemoteHost combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParam' mods sym a :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParams sym a :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryFlag sym :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Header' mods sym a :> sub) -> Swagger Source #

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

IsSecure combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Summary desc :> api) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Description desc :> api) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Capture' mods sym a :> sub) -> Swagger Source #

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

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

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (CaptureAll sym a :> sub) -> Swagger Source #

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

Vault combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Vault :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (sym :> sub) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs NoContent) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs a) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs NoContent)) -> Swagger Source #

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

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs a)) -> Swagger Source #

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

Since: 1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Stream method status fr ct a) -> Swagger Source #

subOperations Source #

Arguments

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

Part of a servant API.

-> Proxy api

The whole servant API.

-> Traversal' Swagger Operation 

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

mkEndpoint Source #

Arguments

:: (ToSchema a, AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) 
=> FilePath

Endpoint path.

-> proxy (Verb method status cs (Headers hs a))

Method, content-types, headers and response.

-> Swagger 

Make a singleton Swagger spec (with only one endpoint). For endpoints with no content see mkEndpointNoContent.

mkEndpointNoContent Source #

Arguments

:: (AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) 
=> FilePath

Endpoint path.

-> proxy (Verb method status cs (Headers hs nocontent))

Method, content-types, headers and response.

-> Swagger 

Make a singletone Swagger spec (with only one endpoint) and with no content schema.

mkEndpointWithSchemaRef :: forall cs hs proxy method status a. (AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => Maybe (Referenced Schema) -> FilePath -> proxy (Verb method status cs (Headers hs a)) -> Swagger Source #

Like mkEndpoint but with explicit schema reference. Unlike mkEndpoint this function does not update definitions.

mkEndpointNoContentVerb Source #

Arguments

:: SwaggerMethod method 
=> FilePath

Endpoint path.

-> proxy (NoContentVerb method)

Method

-> Swagger 

addParam :: Param -> Swagger -> Swagger Source #

Add parameter to every operation in the spec.

addConsumes :: [MediaType] -> Swagger -> Swagger Source #

Add accepted content types to every operation in the spec.

markdownCode :: Text -> Text Source #

Format given text as inline code in Markdown.

class SwaggerMethod method where Source #

Methods, available for Swagger.

Methods

swaggerMethod :: proxy method -> Lens' PathItem (Maybe Operation) Source #

class AllAccept cs where Source #

Instances
AllAccept ([] :: [k]) Source # 
Instance details

Defined in Servant.Swagger.Internal

(Accept c, AllAccept cs) => AllAccept (c ': cs :: [a]) Source # 
Instance details

Defined in Servant.Swagger.Internal

Methods

allContentType :: Proxy (c ': cs) -> [MediaType] Source #

class ToResponseHeader h where Source #

Instances
(KnownSymbol sym, ToParamSchema a) => ToResponseHeader (Header sym a :: Type) Source # 
Instance details

Defined in Servant.Swagger.Internal