| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Swagger.Internal
- 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
- addParam :: Param -> Swagger -> Swagger
- addConsumes :: [MediaType] -> Swagger -> Swagger
- markdownCode :: Text -> Text
- addDefaultResponse404 :: ParamName -> Swagger -> Swagger
- addDefaultResponse400 :: ParamName -> Swagger -> Swagger
- class SwaggerMethod method where
- class AllAccept cs where
- class ToResponseHeader h where
- 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)
Minimal complete definition
Methods
toSwagger :: Proxy api -> Swagger Source #
Generate a Swagger specification for a servant API.
Instances
| HasSwagger * Raw Source # | |
| (HasSwagger * a, HasSwagger * b) => HasSwagger * ((:<|>) a b) Source # | |
| HasSwagger * sub => HasSwagger * (WithNamedContext x c sub) Source # |
|
| (ToSchema a, AllAccept [*] cs, HasSwagger k sub) => HasSwagger * ((:>) k * (ReqBody * cs a) sub) Source # | |
| (KnownSymbol sym, ToParamSchema a, HasSwagger k sub) => HasSwagger * ((:>) k * (Header sym a) sub) Source # | |
| (KnownSymbol sym, HasSwagger k sub) => HasSwagger * ((:>) k * (QueryFlag sym) sub) Source # | |
| (KnownSymbol sym, ToParamSchema a, HasSwagger k sub) => HasSwagger * ((:>) k * (QueryParams * sym a) sub) Source # | |
| (KnownSymbol sym, ToParamSchema a, HasSwagger k sub) => HasSwagger * ((:>) k * (QueryParam * sym a) sub) Source # | |
| (KnownSymbol sym, ToParamSchema a, HasSwagger k sub) => HasSwagger * ((:>) k * (CaptureAll * sym a) sub) Source # | Swagger Spec doesn't have a notion of CaptureAll, this instance is the best effort. |
| (KnownSymbol sym, ToParamSchema a, HasSwagger k sub) => HasSwagger * ((:>) k * (Capture * sym a) sub) Source # | |
| (KnownSymbol sym, HasSwagger k sub) => HasSwagger * ((:>) k Symbol sym sub) Source # | |
| HasSwagger k sub => HasSwagger * ((:>) k * HttpVersion sub) Source # |
|
| HasSwagger k sub => HasSwagger * ((:>) k * RemoteHost sub) Source # |
|
| HasSwagger k sub => HasSwagger * ((:>) k * IsSecure sub) Source # |
|
| HasSwagger k sub => HasSwagger * ((:>) k * Vault sub) Source # |
|
| (AllAccept [*] cs, AllToResponseHeader [*] hs, KnownNat status, SwaggerMethod k1 method) => HasSwagger * (Verb * k1 method status cs (Headers hs NoContent)) Source # | |
| (AllAccept [*] cs, KnownNat status, SwaggerMethod k1 method) => HasSwagger * (Verb * k1 method status cs NoContent) Source # | |
| (ToSchema a, AllAccept [*] cs, AllToResponseHeader [*] hs, KnownNat status, SwaggerMethod k1 method) => HasSwagger * (Verb * k1 method status cs (Headers hs a)) Source # | |
| (ToSchema a, AllAccept [*] cs, KnownNat status, SwaggerMethod k1 method) => HasSwagger * (Verb * k1 method status cs a) 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 but ensures that operations
indeed belong to the API at compile time.operationsOf
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.
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 but with explicit schema reference.
Unlike mkEndpoint this function does not update mkEndpoint.definitions
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 AllAccept cs where Source #
Minimal complete definition
Methods
allContentType :: Proxy cs -> [MediaType] Source #
class ToResponseHeader h where Source #
Minimal complete definition
Methods
toResponseHeader :: Proxy h -> (HeaderName, Header) Source #
Instances
| (KnownSymbol sym, ToParamSchema a) => ToResponseHeader * (Header sym a) Source # | |
class AllToResponseHeader hs where Source #
Minimal complete definition
Methods
toAllResponseHeaders :: Proxy hs -> InsOrdHashMap HeaderName Header Source #
Instances
| AllToResponseHeader [k] ([] k) Source # | |
| AllToResponseHeader [*] hs => AllToResponseHeader * (HList hs) Source # | |
| (ToResponseHeader a h, AllToResponseHeader [a] hs) => AllToResponseHeader [a] ((:) a h hs) Source # | |