Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class HasSwagger api where
- subOperations :: (IsSubAPI sub api, HasSwagger sub) => Proxy sub -> Proxy api -> Traversal' Swagger Operation
- mkEndpoint :: forall a cs hs proxy method status. (ToSchema a, AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs a)) -> Swagger
- mkEndpointNoContent :: forall nocontent cs hs proxy method status. (AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs nocontent)) -> Swagger
- 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
- mkEndpointNoContentVerb :: forall proxy method. SwaggerMethod method => FilePath -> proxy (NoContentVerb method) -> Swagger
- addParam :: Param -> Swagger -> Swagger
- addConsumes :: [MediaType] -> Swagger -> Swagger
- markdownCode :: Text -> Text
- addDefaultResponse404 :: ParamName -> Swagger -> Swagger
- addDefaultResponse400 :: ParamName -> Swagger -> Swagger
- class SwaggerMethod method where
- swaggerMethod :: proxy method -> Lens' PathItem (Maybe Operation)
- class AllAccept cs where
- allContentType :: Proxy cs -> [MediaType]
- class ToResponseHeader h where
- toResponseHeader :: Proxy h -> (HeaderName, Header)
- class AllToResponseHeader hs where
Documentation
class HasSwagger api where Source #
Generate a Swagger specification for a servant API.
To generate Swagger specification, your data types need
and/or ToParamSchema
instances.ToSchema
is used for ToParamSchema
, Capture
and QueryParam
.
Header
is used for ToSchema
and response data types.ReqBody
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)
Instances
:: (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
but ensures that operations
indeed belong to the API at compile time.operationsOf
:: (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
.
:: (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
but with explicit schema reference.
Unlike mkEndpoint
this function does not update mkEndpoint
.definitions
mkEndpointNoContentVerb Source #
:: SwaggerMethod method | |
=> FilePath | Endpoint path. |
-> proxy (NoContentVerb method) | Method |
-> Swagger |
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.
Instances
SwaggerMethod PATCH Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod OPTIONS Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod DELETE Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod PUT Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod HEAD Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod POST Source # | |
Defined in Servant.Swagger.Internal | |
SwaggerMethod GET Source # | |
Defined in Servant.Swagger.Internal |
class AllAccept cs where Source #
allContentType :: Proxy cs -> [MediaType] Source #
Instances
AllAccept ([] :: [k]) Source # | |
Defined in Servant.Swagger.Internal allContentType :: Proxy [] -> [MediaType] Source # | |
(Accept c, AllAccept cs) => AllAccept (c ': cs :: [a]) Source # | |
Defined in Servant.Swagger.Internal allContentType :: Proxy (c ': cs) -> [MediaType] Source # |
class ToResponseHeader h where Source #
toResponseHeader :: Proxy h -> (HeaderName, Header) Source #
Instances
(KnownSymbol sym, ToParamSchema a) => ToResponseHeader (Header sym a :: Type) Source # | |
Defined in Servant.Swagger.Internal toResponseHeader :: Proxy (Header sym a) -> (HeaderName, Header0) Source # |
class AllToResponseHeader hs where Source #
Instances
AllToResponseHeader ([] :: [k]) Source # | |
Defined in Servant.Swagger.Internal | |
AllToResponseHeader hs => AllToResponseHeader (HList hs :: Type) Source # | |
Defined in Servant.Swagger.Internal toAllResponseHeaders :: Proxy (HList hs) -> InsOrdHashMap HeaderName Header Source # | |
(ToResponseHeader h, AllToResponseHeader hs) => AllToResponseHeader (h ': hs :: [a]) Source # | |
Defined in Servant.Swagger.Internal toAllResponseHeaders :: Proxy (h ': hs) -> InsOrdHashMap HeaderName Header Source # |