| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.OpenApi.Internal
Contents
Synopsis
- class HasOpenApi api where
- subOperations :: (IsSubAPI sub api, HasOpenApi sub) => Proxy sub -> Proxy api -> Traversal' OpenApi Operation
- mkEndpoint :: forall a cs hs proxy method status. (ToSchema a, AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs a)) -> OpenApi
- mkEndpointNoContent :: forall nocontent cs hs proxy method status. (AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs nocontent)) -> OpenApi
- mkEndpointWithSchemaRef :: forall cs hs proxy method status a. (AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) => Maybe (Referenced Schema) -> FilePath -> proxy (Verb method status cs (Headers hs a)) -> OpenApi
- mkEndpointNoContentVerb :: forall proxy method. OpenApiMethod method => FilePath -> proxy (NoContentVerb method) -> OpenApi
- addParam :: Param -> OpenApi -> OpenApi
- addRequestBody :: RequestBody -> OpenApi -> OpenApi
- markdownCode :: Text -> Text
- addDefaultResponse404 :: ParamName -> OpenApi -> OpenApi
- addDefaultResponse400 :: ParamName -> OpenApi -> OpenApi
- class OpenApiMethod method where- openApiMethod :: 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 HasOpenApi api where Source #
Generate a OpenApi specification for a servant API.
To generate OpenApi specification, your data types need
 ToParamSchemaToSchema
ToParamSchemaCaptureQueryParamHeaderToSchemaReqBody
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
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
Arguments
| :: forall a cs hs proxy method status. (ToSchema a, AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) | |
| => FilePath | Endpoint path. | 
| -> proxy (Verb method status cs (Headers hs a)) | Method, content-types, headers and response. | 
| -> OpenApi | 
Make a singleton OpenApi spec (with only one endpoint).
 For endpoints with no content see mkEndpointNoContent.
Arguments
| :: forall nocontent cs hs proxy method status. (AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) | |
| => FilePath | Endpoint path. | 
| -> proxy (Verb method status cs (Headers hs nocontent)) | Method, content-types, headers and response. | 
| -> OpenApi | 
Make a singletone OpenApi spec (with only one endpoint) and with no content schema.
mkEndpointWithSchemaRef :: forall cs hs proxy method status a. (AllAccept cs, AllToResponseHeader hs, OpenApiMethod method, KnownNat status) => Maybe (Referenced Schema) -> FilePath -> proxy (Verb method status cs (Headers hs a)) -> OpenApi Source #
Like mkEndpointmkEndpointdefinitions
mkEndpointNoContentVerb Source #
Arguments
| :: forall proxy method. OpenApiMethod method | |
| => FilePath | Endpoint path. | 
| -> proxy (NoContentVerb method) | Method | 
| -> OpenApi | 
addRequestBody :: RequestBody -> OpenApi -> OpenApi Source #
Add RequestBody to every operations in the spec.
markdownCode :: Text -> Text Source #
Format given text as inline code in Markdown.
class OpenApiMethod method where Source #
Methods, available for OpenApi.
Instances
| OpenApiMethod 'PATCH Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'OPTIONS Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'DELETE Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'PUT Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'HEAD Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'POST Source # | |
| Defined in Servant.OpenApi.Internal | |
| OpenApiMethod 'GET Source # | |
| Defined in Servant.OpenApi.Internal | |
class AllAccept cs where Source #
Methods
allContentType :: Proxy cs -> [MediaType] Source #
Instances
| AllAccept ('[] :: [k]) Source # | |
| Defined in Servant.OpenApi.Internal Methods allContentType :: Proxy '[] -> [MediaType] Source # | |
| (Accept c, AllAccept cs) => AllAccept (c ': cs :: [a]) Source # | |
| Defined in Servant.OpenApi.Internal Methods allContentType :: Proxy (c ': cs) -> [MediaType] Source # | |
class ToResponseHeader h where Source #
Methods
toResponseHeader :: Proxy h -> (HeaderName, Header) Source #
Instances
| (KnownSymbol sym, ToParamSchema a) => ToResponseHeader (Header sym a :: Type) Source # | |
| Defined in Servant.OpenApi.Internal Methods toResponseHeader :: Proxy (Header sym a) -> (HeaderName, Header0) Source # | |
class AllToResponseHeader hs where Source #
Methods
toAllResponseHeaders :: Proxy hs -> InsOrdHashMap HeaderName Header Source #
Instances
| AllToResponseHeader ('[] :: [k]) Source # | |
| Defined in Servant.OpenApi.Internal Methods toAllResponseHeaders :: Proxy '[] -> InsOrdHashMap HeaderName Header Source # | |
| AllToResponseHeader hs => AllToResponseHeader (HList hs :: Type) Source # | |
| Defined in Servant.OpenApi.Internal Methods toAllResponseHeaders :: Proxy (HList hs) -> InsOrdHashMap HeaderName Header Source # | |
| (ToResponseHeader h, AllToResponseHeader hs) => AllToResponseHeader (h ': hs :: [a]) Source # | |
| Defined in Servant.OpenApi.Internal Methods toAllResponseHeaders :: Proxy (h ': hs) -> InsOrdHashMap HeaderName Header Source # | |
Orphan instances
| ToSchema a => ToSchema (WithStatus s a) Source # | |
| Methods declareNamedSchema :: Proxy (WithStatus s a) -> Declare (Definitions Schema) NamedSchema # | |