Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.OpenApi.Internal
Contents
Synopsis
- type Definitions = InsOrdHashMap Text
- data OpenApi = OpenApi {}
- lowerOpenApiSpecVersion :: Version
- upperOpenApiSpecVersion :: Version
- data Info = Info {}
- data Contact = Contact {}
- data License = License {
- _licenseName :: Text
- _licenseUrl :: Maybe URL
- data Server = Server {}
- data ServerVariable = ServerVariable {}
- data Components = Components {
- _componentsSchemas :: Definitions Schema
- _componentsResponses :: Definitions Response
- _componentsParameters :: Definitions Param
- _componentsExamples :: Definitions Example
- _componentsRequestBodies :: Definitions RequestBody
- _componentsHeaders :: Definitions Header
- _componentsSecuritySchemes :: SecurityDefinitions
- _componentsLinks :: Definitions Link
- _componentsCallbacks :: Definitions Callback
- data PathItem = PathItem {
- _pathItemSummary :: Maybe Text
- _pathItemDescription :: Maybe Text
- _pathItemGet :: Maybe Operation
- _pathItemPut :: Maybe Operation
- _pathItemPost :: Maybe Operation
- _pathItemDelete :: Maybe Operation
- _pathItemOptions :: Maybe Operation
- _pathItemHead :: Maybe Operation
- _pathItemPatch :: Maybe Operation
- _pathItemTrace :: Maybe Operation
- _pathItemServers :: [Server]
- _pathItemParameters :: [Referenced Param]
- data Operation = Operation {
- _operationTags :: InsOrdHashSet TagName
- _operationSummary :: Maybe Text
- _operationDescription :: Maybe Text
- _operationExternalDocs :: Maybe ExternalDocs
- _operationOperationId :: Maybe Text
- _operationParameters :: [Referenced Param]
- _operationRequestBody :: Maybe (Referenced RequestBody)
- _operationResponses :: Responses
- _operationCallbacks :: InsOrdHashMap Text (Referenced Callback)
- _operationDeprecated :: Maybe Bool
- _operationSecurity :: [SecurityRequirement]
- _operationServers :: [Server]
- mediaTypeConstr :: Constr
- mediaTypeData :: DataType
- data RequestBody = RequestBody {}
- data MediaTypeObject = MediaTypeObject {}
- data Style
- data Encoding = Encoding {}
- newtype MimeList = MimeList {
- getMimeList :: [MediaType]
- mimeListConstr :: Constr
- mimeListDataType :: DataType
- data Param = Param {
- _paramName :: Text
- _paramDescription :: Maybe Text
- _paramRequired :: Maybe Bool
- _paramDeprecated :: Maybe Bool
- _paramIn :: ParamLocation
- _paramAllowEmptyValue :: Maybe Bool
- _paramAllowReserved :: Maybe Bool
- _paramSchema :: Maybe (Referenced Schema)
- _paramStyle :: Maybe Style
- _paramExplode :: Maybe Bool
- _paramExample :: Maybe Value
- _paramExamples :: InsOrdHashMap Text (Referenced Example)
- data Example = Example {}
- data ExpressionOrValue
- = Expression Text
- | Value Value
- data Link = Link {}
- data OpenApiItems where
- data OpenApiType where
- data ParamLocation
- type Format = Text
- type ParamName = Text
- data Schema = Schema {
- _schemaTitle :: Maybe Text
- _schemaDescription :: Maybe Text
- _schemaRequired :: [ParamName]
- _schemaNullable :: Maybe Bool
- _schemaAllOf :: Maybe [Referenced Schema]
- _schemaOneOf :: Maybe [Referenced Schema]
- _schemaNot :: Maybe (Referenced Schema)
- _schemaAnyOf :: Maybe [Referenced Schema]
- _schemaProperties :: InsOrdHashMap Text (Referenced Schema)
- _schemaAdditionalProperties :: Maybe AdditionalProperties
- _schemaDiscriminator :: Maybe Discriminator
- _schemaReadOnly :: Maybe Bool
- _schemaWriteOnly :: Maybe Bool
- _schemaXml :: Maybe Xml
- _schemaExternalDocs :: Maybe ExternalDocs
- _schemaExample :: Maybe Value
- _schemaDeprecated :: Maybe Bool
- _schemaMaxProperties :: Maybe Integer
- _schemaMinProperties :: Maybe Integer
- _schemaDefault :: Maybe Value
- _schemaType :: Maybe OpenApiType
- _schemaFormat :: Maybe Format
- _schemaItems :: Maybe OpenApiItems
- _schemaMaximum :: Maybe Scientific
- _schemaExclusiveMaximum :: Maybe Bool
- _schemaMinimum :: Maybe Scientific
- _schemaExclusiveMinimum :: Maybe Bool
- _schemaMaxLength :: Maybe Integer
- _schemaMinLength :: Maybe Integer
- _schemaPattern :: Maybe Pattern
- _schemaMaxItems :: Maybe Integer
- _schemaMinItems :: Maybe Integer
- _schemaUniqueItems :: Maybe Bool
- _schemaEnum :: Maybe [Value]
- _schemaMultipleOf :: Maybe Scientific
- type Pattern = Text
- data Discriminator = Discriminator {}
- data NamedSchema = NamedSchema {}
- data Xml = Xml {
- _xmlName :: Maybe Text
- _xmlNamespace :: Maybe Text
- _xmlPrefix :: Maybe Text
- _xmlAttribute :: Maybe Bool
- _xmlWrapped :: Maybe Bool
- data Responses = Responses {}
- type HttpStatusCode = Int
- data Response = Response {}
- newtype Callback = Callback (InsOrdHashMap Text PathItem)
- type HeaderName = Text
- data Header = Header {}
- data ApiKeyLocation
- data ApiKeyParams = ApiKeyParams {}
- type AuthorizationURL = Text
- type TokenURL = Text
- newtype OAuth2ImplicitFlow = OAuth2ImplicitFlow {}
- newtype OAuth2PasswordFlow = OAuth2PasswordFlow {}
- newtype OAuth2ClientCredentialsFlow = OAuth2ClientCredentialsFlow {}
- data OAuth2AuthorizationCodeFlow = OAuth2AuthorizationCodeFlow {}
- data OAuth2Flow p = OAuth2Flow {}
- data OAuth2Flows = OAuth2Flows {}
- type BearerFormat = Text
- data HttpSchemeType
- data SecuritySchemeType
- data SecurityScheme = SecurityScheme {}
- newtype SecurityDefinitions = SecurityDefinitions (Definitions SecurityScheme)
- newtype SecurityRequirement = SecurityRequirement {}
- type TagName = Text
- data Tag = Tag {}
- data ExternalDocs = ExternalDocs {}
- newtype Reference = Reference {
- getReference :: Text
- data Referenced a
- newtype URL = URL {}
- data AdditionalProperties
- newtype OpenApiSpecVersion = OpenApiSpecVersion {}
- referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
- referencedParseJSON :: FromJSON a => Text -> Value -> Parser (Referenced a)
Documentation
>>>
:seti -XDataKinds
>>>
import Data.Aeson
>>>
import Data.ByteString.Lazy.Char8 as BSL
>>>
import Data.OpenApi.Internal.Utils
type Definitions = InsOrdHashMap Text Source #
A list of definitions that can be used in references.
This is the root document object for the API specification.
Constructors
OpenApi | |
Fields
|
Instances
lowerOpenApiSpecVersion :: Version Source #
This is the lower version of the OpenApi Spec this library can parse or produce
upperOpenApiSpecVersion :: Version Source #
This is the upper version of the OpenApi Spec this library can parse or produce
The object provides metadata about the API. The metadata MAY be used by the clients if needed, and MAY be presented in editing or documentation generation tools for convenience.
Constructors
Info | |
Fields
|
Instances
Contact information for the exposed API.
Constructors
Contact | |
Fields
|
Instances
License information for the exposed API.
Constructors
License | |
Fields
|
Instances
FromJSON License Source # | |
ToJSON License Source # | |
Defined in Data.OpenApi.Internal | |
Data License Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> License -> c License # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c License # toConstr :: License -> Constr # dataTypeOf :: License -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c License) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License) # gmapT :: (forall b. Data b => b -> b) -> License -> License # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQ :: (forall d. Data d => d -> u) -> License -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> License -> m License # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # | |
IsString License Source # | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> License # | |
Generic License Source # | |
Show License Source # | |
Eq License Source # | |
HasName License Text Source # | |
(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "name" k License License a b Source # | |
Defined in Data.OpenApi.Optics | |
(k ~ A_Lens, a ~ Maybe URL, b ~ Maybe URL) => LabelOptic "url" k License License a b Source # | |
Defined in Data.OpenApi.Optics | |
HasLicense Info (Maybe License) Source # | |
HasUrl License (Maybe URL) Source # | |
type Rep License Source # | |
Defined in Data.OpenApi.Internal type Rep License = D1 ('MetaData "License" "Data.OpenApi.Internal" "openapi3-3.2.3-1GDWKFdjVUVI26l6xU7yLu" 'False) (C1 ('MetaCons "License" 'PrefixI 'True) (S1 ('MetaSel ('Just "_licenseName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_licenseUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe URL)))) |
An object representing a Server.
Constructors
Server | |
Fields
|
Instances
data ServerVariable Source #
Constructors
ServerVariable | |
Fields
|
Instances
data Components Source #
Holds a set of reusable objects for different aspects of the OAS. All objects defined within the components object will have no effect on the API unless they are explicitly referenced from properties outside the components object.
Constructors
Instances
Describes the operations available on a single path.
A
may be empty, due to ACL constraints.
The path itself is still exposed to the documentation viewer
but they will not know which operations and parameters are available.PathItem
Constructors
PathItem | |
Fields
|
Instances
Describes a single API operation on a path.
Constructors
Operation | |
Fields
|
Instances
data RequestBody Source #
Describes a single request body.
Constructors
RequestBody | |
Fields
|
Instances
data MediaTypeObject Source #
Each Media Type Object provides schema and examples for the media type identified by its key.
Constructors
MediaTypeObject | |
Fields
|
Instances
In order to support common ways of serializing simple parameters, a set of style values are defined.
Constructors
StyleMatrix | Path-style parameters defined by RFC6570. |
StyleLabel | Label style parameters defined by RFC6570. |
StyleForm | Form style parameters defined by RFC6570.
This option replaces |
StyleSimple | Simple style parameters defined by RFC6570.
This option replaces |
StyleSpaceDelimited | Space separated array values.
This option replaces |
StylePipeDelimited | Pipe separated array values.
This option replaces |
StyleDeepObject | Provides a simple way of rendering nested objects using form parameters. |
Instances
FromJSON Style Source # | |
ToJSON Style Source # | |
Defined in Data.OpenApi.Internal | |
Data Style Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Style -> c Style # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style # dataTypeOf :: Style -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Style) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) # gmapT :: (forall b. Data b => b -> b) -> Style -> Style # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r # gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style # | |
Generic Style Source # | |
Show Style Source # | |
Eq Style Source # | |
HasStyle Encoding (Maybe Style) Source # | |
HasStyle Param (Maybe Style) Source # | |
type Rep Style Source # | |
Defined in Data.OpenApi.Internal type Rep Style = D1 ('MetaData "Style" "Data.OpenApi.Internal" "openapi3-3.2.3-1GDWKFdjVUVI26l6xU7yLu" 'False) ((C1 ('MetaCons "StyleMatrix" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StyleLabel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StyleForm" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StyleSimple" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StyleSpaceDelimited" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StylePipeDelimited" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StyleDeepObject" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Constructors
Encoding | |
Fields
|
Instances
Constructors
MimeList | |
Fields
|
Instances
FromJSON MimeList Source # | |
ToJSON MimeList Source # | |
Defined in Data.OpenApi.Internal | |
Data MimeList Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MimeList -> c MimeList # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MimeList # toConstr :: MimeList -> Constr # dataTypeOf :: MimeList -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MimeList) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MimeList) # gmapT :: (forall b. Data b => b -> b) -> MimeList -> MimeList # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MimeList -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MimeList -> r # gmapQ :: (forall d. Data d => d -> u) -> MimeList -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MimeList -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList # | |
Monoid MimeList Source # | |
Semigroup MimeList Source # | |
Show MimeList Source # | |
Eq MimeList Source # | |
AesonDefaultValue MimeList Source # | |
Defined in Data.OpenApi.Internal Methods | |
SwaggerMonoid MimeList Source # | |
Defined in Data.OpenApi.Internal Methods |
Describes a single operation parameter. A unique parameter is defined by a combination of a name and location.
Constructors
Param | |
Fields
|
Instances
Constructors
Example | |
Fields
|
Instances
data ExpressionOrValue Source #
Constructors
Expression Text | |
Value Value |
Instances
The Link object represents a possible design-time link for a response. The presence of a link does not guarantee the caller's ability to successfully invoke it, rather it provides a known relationship and traversal mechanism between responses and other operations.
Constructors
Link | |
Fields
|
Instances
data OpenApiItems where Source #
Items for
schemas.OpenApiArray
Warning: OpenAPI 3.0 does not support tuple arrays. However, OpenAPI 3.1 will, as it will incorporate Json Schema mostly verbatim.
should be used to specify homogenous array OpenApiItemsObject
s.Schema
should be used to specify tuple OpenApiItemsArray
s.Schema
Constructors
OpenApiItemsObject :: Referenced Schema -> OpenApiItems | |
OpenApiItemsArray :: [Referenced Schema] -> OpenApiItems |
Instances
data OpenApiType where Source #
Constructors
Instances
data ParamLocation Source #
Constructors
ParamQuery | Parameters that are appended to the URL.
For example, in |
ParamHeader | Custom headers that are expected as part of the request. |
ParamPath | Used together with Path Templating, where the parameter value is actually part of the operation's URL.
This does not include the host or base path of the API.
For example, in |
ParamCookie | Used to pass a specific cookie value to the API. |
Instances
Constructors
Instances
data Discriminator Source #
Constructors
Discriminator | |
Fields
|
Instances
data NamedSchema Source #
A
with an optional name.
This name can be used in references.Schema
Constructors
NamedSchema | |
Fields |
Instances
Constructors
Xml | |
Fields
|
Instances
A container for the expected responses of an operation. The container maps a HTTP response code to the expected response. It is not expected from the documentation to necessarily cover all possible HTTP response codes, since they may not be known in advance. However, it is expected from the documentation to cover a successful operation response and any known errors.
Constructors
Responses | |
Fields
|
Instances
type HttpStatusCode = Int Source #
Describes a single response from an API Operation.
Constructors
Response | |
Fields
|
Instances
A map of possible out-of band callbacks related to the parent operation.
Each value in the map is a PathItem
Object that describes a set of requests that
may be initiated by the API provider and the expected responses.
The key value used to identify the path item object is an expression, evaluated at runtime,
that identifies a URL to use for the callback operation.
Constructors
Callback (InsOrdHashMap Text PathItem) |
Instances
type HeaderName = Text Source #
Header fields have the same meaning as for Param
.
Style is always treated as StyleSimple
, as it is the only value allowed for headers.
Constructors
Header | |
Fields
|
Instances
data ApiKeyLocation Source #
The location of the API key.
Constructors
ApiKeyQuery | |
ApiKeyHeader | |
ApiKeyCookie |
Instances
data ApiKeyParams Source #
Constructors
ApiKeyParams | |
Fields
|
Instances
type AuthorizationURL = Text Source #
The authorization URL to be used for OAuth2 flow. This SHOULD be in the form of a URL.
The token URL to be used for OAuth2 flow. This SHOULD be in the form of a URL.
newtype OAuth2ImplicitFlow Source #
Constructors
OAuth2ImplicitFlow | |
Instances
newtype OAuth2PasswordFlow Source #
Constructors
OAuth2PasswordFlow | |
Fields |
Instances
newtype OAuth2ClientCredentialsFlow Source #
Constructors
OAuth2ClientCredentialsFlow | |
Instances
data OAuth2AuthorizationCodeFlow Source #
Constructors
OAuth2AuthorizationCodeFlow | |
Instances
data OAuth2Flow p Source #
Constructors
OAuth2Flow | |
Fields
|
Instances
data OAuth2Flows Source #
Constructors
OAuth2Flows | |
Fields
|
Instances
type BearerFormat = Text Source #
data HttpSchemeType Source #
Constructors
HttpSchemeBearer (Maybe BearerFormat) | |
HttpSchemeBasic | |
HttpSchemeCustom Text |
Instances
data SecuritySchemeType Source #
>>>
BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeBearer Nothing))
{ "scheme": "bearer", "type": "http" }
>>>
BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeBearer (Just "jwt")))
{ "bearerFormat": "jwt", "scheme": "bearer", "type": "http" }
>>>
BSL.putStrLn $ encodePretty (SecuritySchemeHttp HttpSchemeBasic)
{ "scheme": "basic", "type": "http" }
>>>
BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeCustom "CANARY"))
{ "scheme": "CANARY", "type": "http" }
>>>
BSL.putStrLn $ encodePretty (SecuritySchemeApiKey (ApiKeyParams "id" ApiKeyCookie))
{ "in": "cookie", "name": "id", "type": "apiKey" }
Constructors
SecuritySchemeHttp HttpSchemeType | |
SecuritySchemeApiKey ApiKeyParams | |
SecuritySchemeOAuth2 OAuth2Flows | |
SecuritySchemeOpenIdConnect URL |
Instances
data SecurityScheme Source #
Constructors
SecurityScheme | |
Fields
|
Instances
newtype SecurityDefinitions Source #
Constructors
SecurityDefinitions (Definitions SecurityScheme) |
Instances
newtype SecurityRequirement Source #
Lists the required security schemes to execute this operation. The object can have multiple security schemes declared in it which are all required (that is, there is a logical AND between the schemes).
Constructors
SecurityRequirement | |
Fields |
Instances
Allows adding meta data to a single tag that is used by Operation
.
It is not mandatory to have a Tag
per tag used there.
Constructors
Tag | |
Fields
|
Instances
FromJSON Tag Source # | |
ToJSON Tag Source # | |
Defined in Data.OpenApi.Internal | |
Data Tag Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag # dataTypeOf :: Tag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) # gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r # gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag # | |
IsString Tag Source # | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> Tag # | |
Generic Tag Source # | |
Show Tag Source # | |
Eq Tag Source # | |
Ord Tag Source # | |
Hashable Tag Source # | |
Defined in Data.OpenApi.Internal | |
HasName Tag TagName Source # | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Tag Tag a b Source # | |
Defined in Data.OpenApi.Optics | |
(k ~ A_Lens, a ~ Maybe ExternalDocs, b ~ Maybe ExternalDocs) => LabelOptic "externalDocs" k Tag Tag a b Source # | |
Defined in Data.OpenApi.Optics | |
(k ~ A_Lens, a ~ TagName, b ~ TagName) => LabelOptic "name" k Tag Tag a b Source # | |
Defined in Data.OpenApi.Optics | |
HasDescription Tag (Maybe Text) Source # | |
Defined in Data.OpenApi.Lens | |
HasExternalDocs Tag (Maybe ExternalDocs) Source # | |
Defined in Data.OpenApi.Lens Methods externalDocs :: Lens' Tag (Maybe ExternalDocs) Source # | |
HasTags OpenApi (InsOrdHashSet Tag) Source # | |
Defined in Data.OpenApi.Lens | |
type Rep Tag Source # | |
Defined in Data.OpenApi.Internal type Rep Tag = D1 ('MetaData "Tag" "Data.OpenApi.Internal" "openapi3-3.2.3-1GDWKFdjVUVI26l6xU7yLu" 'False) (C1 ('MetaCons "Tag" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tagName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TagName) :*: (S1 ('MetaSel ('Just "_tagDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_tagExternalDocs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExternalDocs))))) |
data ExternalDocs Source #
Allows referencing an external resource for extended documentation.
Constructors
ExternalDocs | |
Fields
|
Instances
A simple object to allow referencing other definitions in the specification. It can be used to reference parameters and responses that are defined at the top level for reuse.
Constructors
Reference | |
Fields
|
Instances
FromJSON Reference Source # | |
ToJSON Reference Source # | |
Defined in Data.OpenApi.Internal | |
Data Reference Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Reference -> c Reference # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Reference # toConstr :: Reference -> Constr # dataTypeOf :: Reference -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Reference) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference) # gmapT :: (forall b. Data b => b -> b) -> Reference -> Reference # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r # gmapQ :: (forall d. Data d => d -> u) -> Reference -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Reference -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Reference -> m Reference # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference # | |
Show Reference Source # | |
Eq Reference Source # | |
data Referenced a Source #
Instances
Instances
FromJSON URL Source # | |
ToJSON URL Source # | |
Defined in Data.OpenApi.Internal | |
Data URL Source # | |
Defined in Data.OpenApi.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URL -> c URL # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URL # dataTypeOf :: URL -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URL) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL) # gmapT :: (forall b. Data b => b -> b) -> URL -> URL # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r # gmapQ :: (forall d. Data d => d -> u) -> URL -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URL -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URL -> m URL # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URL -> m URL # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URL -> m URL # | |
Show URL Source # | |
Eq URL Source # | |
Ord URL Source # | |
Hashable URL Source # | |
Defined in Data.OpenApi.Internal | |
SwaggerMonoid URL Source # | |
Defined in Data.OpenApi.Internal | |
HasUrl ExternalDocs URL Source # | |
Defined in Data.OpenApi.Lens | |
HasExternalValue Example (Maybe URL) Source # | |
Defined in Data.OpenApi.Lens | |
HasUrl Contact (Maybe URL) Source # | |
HasUrl License (Maybe URL) Source # | |
data AdditionalProperties Source #
Instances
newtype OpenApiSpecVersion Source #
Constructors
OpenApiSpecVersion | |
Fields |
Instances
referencedToJSON :: ToJSON a => Text -> Referenced a -> Value Source #
referencedParseJSON :: FromJSON a => Text -> Value -> Parser (Referenced a) Source #
Orphan instances
FromJSON MediaType Source # | |
FromJSONKey MediaType Source # | |
Methods | |
ToJSON MediaType Source # | |
ToJSONKey MediaType Source # | |
Data MediaType Source # | |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MediaType -> c MediaType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MediaType # toConstr :: MediaType -> Constr # dataTypeOf :: MediaType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MediaType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MediaType) # gmapT :: (forall b. Data b => b -> b) -> MediaType -> MediaType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MediaType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MediaType -> r # gmapQ :: (forall d. Data d => d -> u) -> MediaType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MediaType -> m MediaType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaType -> m MediaType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaType -> m MediaType # | |
Hashable MediaType Source # | |
AesonDefaultValue Version Source # | |
Methods | |
(Eq a, Hashable a) => SwaggerMonoid (InsOrdHashSet a) Source # | |
Methods swaggerMempty :: InsOrdHashSet a Source # swaggerMappend :: InsOrdHashSet a -> InsOrdHashSet a -> InsOrdHashSet a Source # |