Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Swagger.Internal
Contents
Synopsis
- type Definitions = InsOrdHashMap Text
- data Swagger = Swagger {
- _swaggerInfo :: Info
- _swaggerHost :: Maybe Host
- _swaggerBasePath :: Maybe FilePath
- _swaggerSchemes :: Maybe [Scheme]
- _swaggerConsumes :: MimeList
- _swaggerProduces :: MimeList
- _swaggerPaths :: InsOrdHashMap FilePath PathItem
- _swaggerDefinitions :: Definitions Schema
- _swaggerParameters :: Definitions Param
- _swaggerResponses :: Definitions Response
- _swaggerSecurityDefinitions :: SecurityDefinitions
- _swaggerSecurity :: [SecurityRequirement]
- _swaggerTags :: InsOrdHashSet Tag
- _swaggerExternalDocs :: Maybe ExternalDocs
- data Info = Info {}
- data Contact = Contact {}
- data License = License {
- _licenseName :: Text
- _licenseUrl :: Maybe URL
- data Host = Host {}
- hostConstr :: Constr
- hostDataType :: DataType
- data Scheme
- data PathItem = PathItem {}
- data Operation = Operation {
- _operationTags :: InsOrdHashSet TagName
- _operationSummary :: Maybe Text
- _operationDescription :: Maybe Text
- _operationExternalDocs :: Maybe ExternalDocs
- _operationOperationId :: Maybe Text
- _operationConsumes :: Maybe MimeList
- _operationProduces :: Maybe MimeList
- _operationParameters :: [Referenced Param]
- _operationResponses :: Responses
- _operationSchemes :: Maybe [Scheme]
- _operationDeprecated :: Maybe Bool
- _operationSecurity :: [SecurityRequirement]
- newtype MimeList = MimeList {
- getMimeList :: [MediaType]
- mimeListConstr :: Constr
- mimeListDataType :: DataType
- data Param = Param {}
- data ParamAnySchema
- data ParamOtherSchema = ParamOtherSchema {}
- data SwaggerItems t where
- swaggerItemsPrimitiveConstr :: Constr
- swaggerItemsObjectConstr :: Constr
- swaggerItemsArrayConstr :: Constr
- swaggerItemsDataType :: DataType
- data SwaggerKind t
- type family SwaggerKindType (k :: SwaggerKind *) :: *
- data SwaggerType t where
- swaggerTypeConstr :: Data (SwaggerType t) => SwaggerType t -> Constr
- swaggerTypeDataType :: SwaggerType t -> DataType
- swaggerCommonTypes :: [SwaggerType k]
- swaggerParamTypes :: [SwaggerType SwaggerKindParamOtherSchema]
- swaggerSchemaTypes :: [SwaggerType SwaggerKindSchema]
- swaggerTypeConstrs :: [Constr]
- data ParamLocation
- type Format = Text
- data CollectionFormat t where
- collectionFormatConstr :: CollectionFormat t -> Constr
- collectionFormatDataType :: DataType
- collectionCommonFormats :: [CollectionFormat t]
- type ParamName = Text
- data Schema = Schema {
- _schemaTitle :: Maybe Text
- _schemaDescription :: Maybe Text
- _schemaRequired :: [ParamName]
- _schemaAllOf :: Maybe [Referenced Schema]
- _schemaProperties :: InsOrdHashMap Text (Referenced Schema)
- _schemaAdditionalProperties :: Maybe AdditionalProperties
- _schemaDiscriminator :: Maybe Text
- _schemaReadOnly :: Maybe Bool
- _schemaXml :: Maybe Xml
- _schemaExternalDocs :: Maybe ExternalDocs
- _schemaExample :: Maybe Value
- _schemaMaxProperties :: Maybe Integer
- _schemaMinProperties :: Maybe Integer
- _schemaParamSchema :: ParamSchema SwaggerKindSchema
- data NamedSchema = NamedSchema {}
- type Pattern = Text
- data ParamSchema (t :: SwaggerKind *) = ParamSchema {
- _paramSchemaDefault :: Maybe Value
- _paramSchemaType :: Maybe (SwaggerType t)
- _paramSchemaFormat :: Maybe Format
- _paramSchemaItems :: Maybe (SwaggerItems t)
- _paramSchemaMaximum :: Maybe Scientific
- _paramSchemaExclusiveMaximum :: Maybe Bool
- _paramSchemaMinimum :: Maybe Scientific
- _paramSchemaExclusiveMinimum :: Maybe Bool
- _paramSchemaMaxLength :: Maybe Integer
- _paramSchemaMinLength :: Maybe Integer
- _paramSchemaPattern :: Maybe Pattern
- _paramSchemaMaxItems :: Maybe Integer
- _paramSchemaMinItems :: Maybe Integer
- _paramSchemaUniqueItems :: Maybe Bool
- _paramSchemaEnum :: Maybe [Value]
- _paramSchemaMultipleOf :: Maybe Scientific
- data Xml = Xml {
- _xmlName :: Maybe Text
- _xmlNamespace :: Maybe Text
- _xmlPrefix :: Maybe Text
- _xmlAttribute :: Maybe Bool
- _xmlWrapped :: Maybe Bool
- data Responses = Responses {
- _responsesDefault :: Maybe (Referenced Response)
- _responsesResponses :: InsOrdHashMap HttpStatusCode (Referenced Response)
- type HttpStatusCode = Int
- data Response = Response {
- _responseDescription :: Text
- _responseSchema :: Maybe (Referenced Schema)
- _responseHeaders :: InsOrdHashMap HeaderName Header
- _responseExamples :: Maybe Example
- type HeaderName = Text
- data Header = Header {}
- data Example = Example {
- getExample :: Map MediaType Value
- exampleConstr :: Constr
- exampleDataType :: DataType
- data ApiKeyLocation
- data ApiKeyParams = ApiKeyParams {}
- type AuthorizationURL = Text
- type TokenURL = Text
- data OAuth2Flow
- data OAuth2Params = OAuth2Params {
- _oauth2Flow :: OAuth2Flow
- _oauth2Scopes :: InsOrdHashMap Text Text
- data SecuritySchemeType
- data SecurityScheme = SecurityScheme {}
- mergeSecurityScheme :: SecurityScheme -> SecurityScheme -> SecurityScheme
- newtype SecurityDefinitions = SecurityDefinitions (Definitions SecurityScheme)
- newtype SecurityRequirement = SecurityRequirement {
- getSecurityRequirement :: InsOrdHashMap Text [Text]
- type TagName = Text
- data Tag = Tag {}
- data ExternalDocs = ExternalDocs {}
- newtype Reference = Reference {
- getReference :: Text
- data Referenced a
- newtype URL = URL {}
- data AdditionalProperties
- referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
- referencedParseJSON :: FromJSON a => Text -> Value -> Parser (Referenced a)
Documentation
>>>
:seti -XDataKinds
>>>
import Data.Aeson
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
Swagger | |
Fields
|
Instances
The object provides metadata about the API. The metadata can be used by the clients if needed, and can be presented in the Swagger-UI for convenience.
Constructors
Info | |
Fields
|
Instances
Eq Info Source # | |
Data Info Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Info -> c Info # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Info # dataTypeOf :: Info -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Info) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info) # gmapT :: (forall b. Data b => b -> b) -> Info -> Info # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r # gmapQ :: (forall d. Data d => d -> u) -> Info -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Info -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Info -> m Info # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info # | |
Show Info Source # | |
Generic Info Source # | |
Semigroup Info Source # | |
Monoid Info Source # | |
FromJSON Info Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Info Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Info -> Encoding toJSONList :: [Info] -> Value toEncodingList :: [Info] -> Encoding | |
AesonDefaultValue Info Source # | |
Defined in Data.Swagger.Internal Methods defaultValue :: Maybe Info Source # | |
SwaggerMonoid Info Source # | |
Defined in Data.Swagger.Internal | |
HasInfo Swagger Info Source # | |
HasVersion Info Text Source # | |
HasTitle Info Text Source # | |
(k ~ A_Lens, a ~ Maybe Contact, b ~ Maybe Contact) => LabelOptic "contact" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
(k ~ A_Lens, a ~ Maybe License, b ~ Maybe License) => LabelOptic "license" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "termsOfService" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "title" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "version" k Info Info a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Info Info a b | |
HasTermsOfService Info (Maybe Text) Source # | |
Defined in Data.Swagger.Lens | |
HasLicense Info (Maybe License) Source # | |
HasDescription Info (Maybe Text) Source # | |
Defined in Data.Swagger.Lens | |
HasContact Info (Maybe Contact) Source # | |
type Rep Info Source # | |
Defined in Data.Swagger.Internal type Rep Info = D1 (MetaData "Info" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Info" PrefixI True) ((S1 (MetaSel (Just "_infoTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "_infoDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_infoTermsOfService") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_infoContact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Contact)) :*: (S1 (MetaSel (Just "_infoLicense") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe License)) :*: S1 (MetaSel (Just "_infoVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))) |
Contact information for the exposed API.
Constructors
Contact | |
Fields
|
Instances
Eq Contact Source # | |
Data Contact Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Contact -> c Contact # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Contact # toConstr :: Contact -> Constr # dataTypeOf :: Contact -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Contact) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact) # gmapT :: (forall b. Data b => b -> b) -> Contact -> Contact # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Contact -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Contact -> r # gmapQ :: (forall d. Data d => d -> u) -> Contact -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Contact -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Contact -> m Contact # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Contact -> m Contact # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Contact -> m Contact # | |
Show Contact Source # | |
Generic Contact Source # | |
Semigroup Contact Source # | |
Monoid Contact Source # | |
FromJSON Contact Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Contact Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Contact -> Encoding toJSONList :: [Contact] -> Value toEncodingList :: [Contact] -> Encoding | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "email" k Contact Contact a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Contact Contact a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "name" k Contact Contact a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Contact Contact a b | |
(k ~ A_Lens, a ~ Maybe URL, b ~ Maybe URL) => LabelOptic "url" k Contact Contact a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Contact Contact a b | |
HasName Contact (Maybe Text) Source # | |
HasContact Info (Maybe Contact) Source # | |
HasUrl Contact (Maybe URL) Source # | |
HasEmail Contact (Maybe Text) Source # | |
type Rep Contact Source # | |
Defined in Data.Swagger.Internal type Rep Contact = D1 (MetaData "Contact" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Contact" PrefixI True) (S1 (MetaSel (Just "_contactName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_contactUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URL)) :*: S1 (MetaSel (Just "_contactEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))) |
License information for the exposed API.
Constructors
License | |
Fields
|
Instances
Eq License Source # | |
Data License Source # | |
Defined in Data.Swagger.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 :: (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 # | |
Show License Source # | |
IsString License Source # | |
Defined in Data.Swagger.Internal Methods fromString :: String -> License # | |
Generic License Source # | |
FromJSON License Source # | |
Defined in Data.Swagger.Internal | |
ToJSON License Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: License -> Encoding toJSONList :: [License] -> Value toEncodingList :: [License] -> Encoding | |
HasName License Text Source # | |
(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "name" k License License a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx License License a b | |
(k ~ A_Lens, a ~ Maybe URL, b ~ Maybe URL) => LabelOptic "url" k License License a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx License License a b | |
HasLicense Info (Maybe License) Source # | |
HasUrl License (Maybe URL) Source # | |
type Rep License Source # | |
Defined in Data.Swagger.Internal type Rep License = D1 (MetaData "License" "Data.Swagger.Internal" "swagger2-2.6-inplace" 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)))) |
The host (name or ip) serving the API. It MAY include a port.
Instances
Eq Host Source # | |
Data Host Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Host -> c Host # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Host # dataTypeOf :: Host -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Host) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Host) # gmapT :: (forall b. Data b => b -> b) -> Host -> Host # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Host -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Host -> r # gmapQ :: (forall d. Data d => d -> u) -> Host -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Host -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Host -> m Host # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Host -> m Host # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Host -> m Host # | |
Show Host Source # | |
IsString Host Source # | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Host # | |
Generic Host Source # | |
FromJSON Host Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Host Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Host -> Encoding toJSONList :: [Host] -> Value toEncodingList :: [Host] -> Encoding | |
HasName Host HostName Source # | |
Defined in Data.Swagger.Lens | |
(k ~ A_Lens, a ~ HostName, b ~ HostName) => LabelOptic "name" k Host Host a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Host Host a b | |
(k ~ A_Lens, a ~ Maybe PortNumber, b ~ Maybe PortNumber) => LabelOptic "port" k Host Host a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Host Host a b | |
HasHost Swagger (Maybe Host) Source # | |
HasPort Host (Maybe PortNumber) Source # | |
type Rep Host Source # | |
Defined in Data.Swagger.Internal type Rep Host = D1 (MetaData "Host" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Host" PrefixI True) (S1 (MetaSel (Just "_hostName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HostName) :*: S1 (MetaSel (Just "_hostPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PortNumber)))) |
hostConstr :: Constr Source #
The transfer protocol of the API.
Instances
Eq Scheme Source # | |
Data Scheme Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme # toConstr :: Scheme -> Constr # dataTypeOf :: Scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) # gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # | |
Show Scheme Source # | |
Generic Scheme Source # | |
FromJSON Scheme Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Scheme Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Scheme -> Encoding toJSONList :: [Scheme] -> Value toEncodingList :: [Scheme] -> Encoding | |
HasSchemes Operation (Maybe [Scheme]) Source # | |
HasSchemes Swagger (Maybe [Scheme]) Source # | |
type Rep Scheme Source # | |
Defined in Data.Swagger.Internal type Rep Scheme = D1 (MetaData "Scheme" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) ((C1 (MetaCons "Http" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Https" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ws" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Wss" PrefixI False) (U1 :: Type -> Type))) |
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
Constructors
MimeList | |
Fields
|
Instances
Describes a single operation parameter. A unique parameter is defined by a combination of a name and location.
Constructors
Param | |
Fields
|
Instances
Eq Param Source # | |
Data Param Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Param -> c Param # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Param # dataTypeOf :: Param -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Param) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param) # gmapT :: (forall b. Data b => b -> b) -> Param -> Param # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r # gmapQ :: (forall d. Data d => d -> u) -> Param -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Param -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Param -> m Param # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param # | |
Show Param Source # | |
Generic Param Source # | |
Semigroup Param Source # | |
Monoid Param Source # | |
FromJSON Param Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Param Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Param -> Encoding toJSONList :: [Param] -> Value toEncodingList :: [Param] -> Encoding | |
Generic Param Source # | |
HasDatatypeInfo Param Source # | |
Defined in Data.Swagger.Internal Associated Types type DatatypeInfoOf Param :: DatatypeInfo Methods datatypeInfo :: proxy Param -> DatatypeInfo (Code Param) | |
HasSwaggerAesonOptions Param Source # | |
Defined in Data.Swagger.Internal Methods swaggerAesonOptions :: Proxy Param -> SwaggerAesonOptions Source # aesonDefaults :: Proxy Param -> POP Maybe (Code Param) Source # | |
SwaggerMonoid Param Source # | |
Defined in Data.Swagger.Internal | |
HasName Param Text Source # | |
HasSchema Param ParamAnySchema Source # | |
Defined in Data.Swagger.Lens Methods schema :: Lens' Param ParamAnySchema Source # | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Param Param a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Param Param a b | |
(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "name" k Param Param a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Param Param a b | |
(k ~ A_Lens, a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "required" k Param Param a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Param Param a b | |
(k ~ A_Lens, a ~ ParamAnySchema, b ~ ParamAnySchema) => LabelOptic "schema" k Param Param a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Param Param a b | |
HasParameters Operation [Referenced Param] Source # | |
Defined in Data.Swagger.Lens Methods parameters :: Lens' Operation [Referenced Param] Source # | |
HasParameters PathItem [Referenced Param] Source # | |
Defined in Data.Swagger.Lens Methods parameters :: Lens' PathItem [Referenced Param] Source # | |
HasParameters Swagger (Definitions Param) Source # | |
Defined in Data.Swagger.Lens Methods parameters :: Lens' Swagger (Definitions Param) Source # | |
HasDescription Param (Maybe Text) Source # | |
Defined in Data.Swagger.Lens | |
HasRequired Param (Maybe Bool) Source # | |
FromJSON (Referenced Param) Source # | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (Referenced Param) parseJSONList :: Value -> Parser [Referenced Param] | |
ToJSON (Referenced Param) Source # | |
Defined in Data.Swagger.Internal Methods toJSON :: Referenced Param -> Value toEncoding :: Referenced Param -> Encoding toJSONList :: [Referenced Param] -> Value toEncodingList :: [Referenced Param] -> Encoding | |
type Rep Param Source # | |
Defined in Data.Swagger.Internal type Rep Param = D1 (MetaData "Param" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Param" PrefixI True) ((S1 (MetaSel (Just "_paramName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_paramDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_paramRequired") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_paramSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParamAnySchema)))) | |
type Code Param Source # | |
Defined in Data.Swagger.Internal | |
type DatatypeInfoOf Param Source # | |
Defined in Data.Swagger.Internal type DatatypeInfoOf Param = ADT "Data.Swagger.Internal" "Param" (Record "Param" (FieldInfo "_paramName" ': (FieldInfo "_paramDescription" ': (FieldInfo "_paramRequired" ': (FieldInfo "_paramSchema" ': ([] :: [FieldInfo]))))) ': ([] :: [ConstructorInfo])) ((StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': (StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': (StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': (StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': ([] :: [StrictnessInfo]))))) ': ([] :: [[StrictnessInfo]])) |
data ParamAnySchema Source #
Constructors
ParamBody (Referenced Schema) | |
ParamOther ParamOtherSchema |
Instances
data ParamOtherSchema Source #
Constructors
ParamOtherSchema | |
Fields
|
Instances
data SwaggerItems t where Source #
Items for
schemas.SwaggerArray
should be used only for query params, headers and path pieces.
The SwaggerItemsPrimitive
parameter specifies how elements of an array should be displayed.
Note that CollectionFormat
tfmt
in
specifies format for elements of type SwaggerItemsPrimitive
fmt schemaschema
.
This is different from the original Swagger's Items Object.
should be used to specify homogenous array SwaggerItemsObject
s.Schema
should be used to specify tuple SwaggerItemsArray
s.Schema
Constructors
Instances
data SwaggerKind t Source #
Type used as a kind to avoid overlapping instances.
Constructors
SwaggerKindNormal t | |
SwaggerKindParamOtherSchema | |
SwaggerKindSchema |
type family SwaggerKindType (k :: SwaggerKind *) :: * Source #
Instances
type SwaggerKindType (SwaggerKindParamOtherSchema :: SwaggerKind Type) Source # | |
Defined in Data.Swagger.Internal | |
type SwaggerKindType (SwaggerKindSchema :: SwaggerKind Type) Source # | |
Defined in Data.Swagger.Internal | |
type SwaggerKindType (SwaggerKindNormal t) Source # | |
Defined in Data.Swagger.Internal |
data SwaggerType t where Source #
Constructors
Instances
swaggerTypeConstr :: Data (SwaggerType t) => SwaggerType t -> Constr Source #
swaggerTypeDataType :: SwaggerType t -> DataType Source #
swaggerCommonTypes :: [SwaggerType k] Source #
swaggerTypeConstrs :: [Constr] Source #
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 |
ParamFormData | Used to describe the payload of an HTTP request when either |
Instances
data CollectionFormat t where Source #
Determines the format of the array.
Constructors
Instances
Constructors
Schema | |
Fields
|
Instances
data NamedSchema Source #
A
with an optional name.
This name can be used in references.Schema
Constructors
NamedSchema | |
Fields |
Instances
data ParamSchema (t :: SwaggerKind *) Source #
Constructors
ParamSchema | |
Fields
|
Instances
Constructors
Xml | |
Fields
|
Instances
Eq Xml Source # | |
Data Xml Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xml -> c Xml # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xml # dataTypeOf :: Xml -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Xml) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml) # gmapT :: (forall b. Data b => b -> b) -> Xml -> Xml # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r # gmapQ :: (forall d. Data d => d -> u) -> Xml -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Xml -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xml -> m Xml # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xml -> m Xml # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xml -> m Xml # | |
Show Xml Source # | |
Generic Xml Source # | |
FromJSON Xml Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Xml Source # | |
Defined in Data.Swagger.Internal | |
(k ~ A_Lens, a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "attribute" k Xml Xml a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Xml Xml a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "name" k Xml Xml a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Xml Xml a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "namespace" k Xml Xml a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Xml Xml a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "prefix" k Xml Xml a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Xml Xml a b | |
(k ~ A_Lens, a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "wrapped" k Xml Xml a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Xml Xml a b | |
HasName Xml (Maybe Text) Source # | |
HasXml Schema (Maybe Xml) Source # | |
HasWrapped Xml (Maybe Bool) Source # | |
HasPrefix Xml (Maybe Text) Source # | |
HasNamespace Xml (Maybe Text) Source # | |
HasAttribute Xml (Maybe Bool) Source # | |
type Rep Xml Source # | |
Defined in Data.Swagger.Internal type Rep Xml = D1 (MetaData "Xml" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Xml" PrefixI True) ((S1 (MetaSel (Just "_xmlName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_xmlNamespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_xmlPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_xmlAttribute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_xmlWrapped") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))) |
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
type HeaderName = Text Source #
Constructors
Header | |
Fields
|
Instances
Eq Header Source # | |
Data Header Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Header -> c Header # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Header # toConstr :: Header -> Constr # dataTypeOf :: Header -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Header) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header) # gmapT :: (forall b. Data b => b -> b) -> Header -> Header # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r # gmapQ :: (forall d. Data d => d -> u) -> Header -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Header -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Header -> m Header # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header # | |
Show Header Source # | |
Generic Header Source # | |
Semigroup Header Source # | |
Monoid Header Source # | |
FromJSON Header Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Header Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Header -> Encoding toJSONList :: [Header] -> Value toEncodingList :: [Header] -> Encoding | |
Generic Header Source # | |
HasDatatypeInfo Header Source # | |
Defined in Data.Swagger.Internal Associated Types type DatatypeInfoOf Header :: DatatypeInfo Methods datatypeInfo :: proxy Header -> DatatypeInfo (Code Header) | |
HasSwaggerAesonOptions Header Source # | |
Defined in Data.Swagger.Internal Methods swaggerAesonOptions :: Proxy Header -> SwaggerAesonOptions Source # aesonDefaults :: Proxy Header -> POP Maybe (Code Header) Source # | |
(a ~ Maybe Value, b ~ Maybe Value) => LabelOptic "default" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Header Header a b | |
(a ~ Maybe [Value], b ~ Maybe [Value]) => LabelOptic "enum" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "exclusiveMaximum" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "exclusiveMinimum" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Format, b ~ Maybe Format) => LabelOptic "format" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe (SwaggerItems (SwaggerKindNormal Header)), b ~ Maybe (SwaggerItems (SwaggerKindNormal Header))) => LabelOptic "items" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Integer, b ~ Maybe Integer) => LabelOptic "maxItems" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Integer, b ~ Maybe Integer) => LabelOptic "maxLength" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Scientific, b ~ Maybe Scientific) => LabelOptic "maximum" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Integer, b ~ Maybe Integer) => LabelOptic "minItems" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Integer, b ~ Maybe Integer) => LabelOptic "minLength" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Scientific, b ~ Maybe Scientific) => LabelOptic "minimum" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Scientific, b ~ Maybe Scientific) => LabelOptic "multipleOf" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(k ~ A_Lens, a ~ ParamSchema (SwaggerKindNormal Header), b ~ ParamSchema (SwaggerKindNormal Header)) => LabelOptic "paramSchema" k Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Header Header a b | |
(a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "pattern" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe (SwaggerType (SwaggerKindNormal Header)), b ~ Maybe (SwaggerType (SwaggerKindNormal Header))) => LabelOptic "type" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
(a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "uniqueItems" A_Lens Header Header a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic A_Lens NoIx Header Header a b | |
HasDescription Header (Maybe Text) Source # | |
Defined in Data.Swagger.Lens | |
HasParamSchema Header (ParamSchema (SwaggerKindNormal Header)) Source # | |
Defined in Data.Swagger.Lens Methods paramSchema :: Lens' Header (ParamSchema (SwaggerKindNormal Header)) Source # | |
HasType Header (Maybe (SwaggerType (SwaggerKindNormal Header))) Source # | |
Defined in Data.Swagger.Lens Methods type_ :: Lens' Header (Maybe (SwaggerType (SwaggerKindNormal Header))) Source # | |
HasDefault Header (Maybe Value) Source # | |
HasHeaders Response (InsOrdHashMap HeaderName Header) Source # | |
Defined in Data.Swagger.Lens | |
type Rep Header Source # | |
Defined in Data.Swagger.Internal type Rep Header = D1 (MetaData "Header" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "Header" PrefixI True) (S1 (MetaSel (Just "_headerDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_headerParamSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParamSchema (SwaggerKindNormal Header))))) | |
type Code Header Source # | |
Defined in Data.Swagger.Internal type Code Header = (Maybe Text ': (ParamSchema (SwaggerKindNormal Header) ': ([] :: [Type]))) ': ([] :: [[Type]]) | |
type DatatypeInfoOf Header Source # | |
Defined in Data.Swagger.Internal type DatatypeInfoOf Header = ADT "Data.Swagger.Internal" "Header" (Record "Header" (FieldInfo "_headerDescription" ': (FieldInfo "_headerParamSchema" ': ([] :: [FieldInfo]))) ': ([] :: [ConstructorInfo])) ((StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': (StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': ([] :: [StrictnessInfo]))) ': ([] :: [[StrictnessInfo]])) |
Constructors
Example | |
Fields
|
Instances
Eq Example Source # | |
Data Example Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Example -> c Example # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Example # toConstr :: Example -> Constr # dataTypeOf :: Example -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Example) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example) # gmapT :: (forall b. Data b => b -> b) -> Example -> Example # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Example -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Example -> r # gmapQ :: (forall d. Data d => d -> u) -> Example -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Example -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Example -> m Example # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Example -> m Example # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Example -> m Example # | |
Show Example Source # | |
Generic Example Source # | |
Semigroup Example Source # | |
Monoid Example Source # | |
FromJSON Example Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Example Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Example -> Encoding toJSONList :: [Example] -> Value toEncodingList :: [Example] -> Encoding | |
HasExamples Response (Maybe Example) Source # | |
type Rep Example Source # | |
Defined in Data.Swagger.Internal |
data ApiKeyLocation Source #
The location of the API key.
Constructors
ApiKeyQuery | |
ApiKeyHeader |
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.
data OAuth2Flow Source #
Constructors
OAuth2Implicit AuthorizationURL | |
OAuth2Password TokenURL | |
OAuth2Application TokenURL | |
OAuth2AccessCode AuthorizationURL TokenURL |
Instances
data OAuth2Params Source #
Constructors
OAuth2Params | |
Fields
|
Instances
Eq OAuth2Params Source # | |
Defined in Data.Swagger.Internal | |
Data OAuth2Params Source # | |
Defined in Data.Swagger.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OAuth2Params # toConstr :: OAuth2Params -> Constr # dataTypeOf :: OAuth2Params -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OAuth2Params) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth2Params) # gmapT :: (forall b. Data b => b -> b) -> OAuth2Params -> OAuth2Params # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r # gmapQ :: (forall d. Data d => d -> u) -> OAuth2Params -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth2Params -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params # | |
Show OAuth2Params Source # | |
Defined in Data.Swagger.Internal Methods showsPrec :: Int -> OAuth2Params -> ShowS # show :: OAuth2Params -> String # showList :: [OAuth2Params] -> ShowS # | |
Generic OAuth2Params Source # | |
Defined in Data.Swagger.Internal Associated Types type Rep OAuth2Params :: Type -> Type # | |
FromJSON OAuth2Params Source # | |
Defined in Data.Swagger.Internal | |
ToJSON OAuth2Params Source # | |
Defined in Data.Swagger.Internal Methods toJSON :: OAuth2Params -> Value toEncoding :: OAuth2Params -> Encoding toJSONList :: [OAuth2Params] -> Value toEncodingList :: [OAuth2Params] -> Encoding | |
Generic OAuth2Params Source # | |
Defined in Data.Swagger.Internal Associated Types type Code OAuth2Params :: [[Type]] | |
HasDatatypeInfo OAuth2Params Source # | |
Defined in Data.Swagger.Internal Associated Types type DatatypeInfoOf OAuth2Params :: DatatypeInfo Methods datatypeInfo :: proxy OAuth2Params -> DatatypeInfo (Code OAuth2Params) | |
HasSwaggerAesonOptions OAuth2Params Source # | |
Defined in Data.Swagger.Internal Methods swaggerAesonOptions :: Proxy OAuth2Params -> SwaggerAesonOptions Source # aesonDefaults :: Proxy OAuth2Params -> POP Maybe (Code OAuth2Params) Source # | |
type Rep OAuth2Params Source # | |
Defined in Data.Swagger.Internal type Rep OAuth2Params = D1 (MetaData "OAuth2Params" "Data.Swagger.Internal" "swagger2-2.6-inplace" False) (C1 (MetaCons "OAuth2Params" PrefixI True) (S1 (MetaSel (Just "_oauth2Flow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OAuth2Flow) :*: S1 (MetaSel (Just "_oauth2Scopes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap Text Text)))) | |
type Code OAuth2Params Source # | |
Defined in Data.Swagger.Internal type Code OAuth2Params = (OAuth2Flow ': (InsOrdHashMap Text Text ': ([] :: [Type]))) ': ([] :: [[Type]]) | |
type DatatypeInfoOf OAuth2Params Source # | |
Defined in Data.Swagger.Internal type DatatypeInfoOf OAuth2Params = ADT "Data.Swagger.Internal" "OAuth2Params" (Record "OAuth2Params" (FieldInfo "_oauth2Flow" ': (FieldInfo "_oauth2Scopes" ': ([] :: [FieldInfo]))) ': ([] :: [ConstructorInfo])) ((StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': (StrictnessInfo NoSourceUnpackedness NoSourceStrictness DecidedLazy ': ([] :: [StrictnessInfo]))) ': ([] :: [[StrictnessInfo]])) |
data SecuritySchemeType Source #
Instances
data SecurityScheme Source #
Constructors
SecurityScheme | |
Fields
|
Instances
mergeSecurityScheme :: SecurityScheme -> SecurityScheme -> SecurityScheme Source #
merge scopes of two OAuth2 security schemes when their flows are identical. In other case returns first security scheme
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
Eq Tag Source # | |
Data Tag Source # | |
Defined in Data.Swagger.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 :: (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 # | |
Ord Tag Source # | |
Show Tag Source # | |
IsString Tag Source # | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Tag # | |
Generic Tag Source # | |
FromJSON Tag Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Tag Source # | |
Defined in Data.Swagger.Internal | |
Hashable Tag Source # | |
Defined in Data.Swagger.Internal | |
HasName Tag TagName Source # | |
(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Tag Tag a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Tag Tag a b | |
(k ~ A_Lens, a ~ Maybe ExternalDocs, b ~ Maybe ExternalDocs) => LabelOptic "externalDocs" k Tag Tag a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Tag Tag a b | |
(k ~ A_Lens, a ~ TagName, b ~ TagName) => LabelOptic "name" k Tag Tag a b | |
Defined in Data.Swagger.Optics Methods labelOptic :: Optic k NoIx Tag Tag a b | |
HasTags Swagger (InsOrdHashSet Tag) Source # | |
HasExternalDocs Tag (Maybe ExternalDocs) Source # | |
Defined in Data.Swagger.Lens Methods externalDocs :: Lens' Tag (Maybe ExternalDocs) Source # | |
HasDescription Tag (Maybe Text) Source # | |
Defined in Data.Swagger.Lens | |
type Rep Tag Source # | |
Defined in Data.Swagger.Internal type Rep Tag = D1 (MetaData "Tag" "Data.Swagger.Internal" "swagger2-2.6-inplace" 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
Eq Reference Source # | |
Data Reference Source # | |
Defined in Data.Swagger.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 :: (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 # | |
FromJSON Reference Source # | |
Defined in Data.Swagger.Internal | |
ToJSON Reference Source # | |
Defined in Data.Swagger.Internal Methods toEncoding :: Reference -> Encoding toJSONList :: [Reference] -> Value toEncodingList :: [Reference] -> Encoding |
data Referenced a Source #
Instances
Instances
Eq URL Source # | |
Data URL Source # | |
Defined in Data.Swagger.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 :: (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 # | |
Ord URL Source # | |
Show URL Source # | |
FromJSON URL Source # | |
Defined in Data.Swagger.Internal | |
ToJSON URL Source # | |
Defined in Data.Swagger.Internal | |
Hashable URL Source # | |
Defined in Data.Swagger.Internal | |
SwaggerMonoid URL Source # | |
Defined in Data.Swagger.Internal | |
HasUrl ExternalDocs URL Source # | |
Defined in Data.Swagger.Lens Methods url :: Lens' ExternalDocs URL Source # | |
HasUrl License (Maybe URL) Source # | |
HasUrl Contact (Maybe URL) Source # | |
data AdditionalProperties Source #
Instances
referencedToJSON :: ToJSON a => Text -> Referenced a -> Value Source #
referencedParseJSON :: FromJSON a => Text -> Value -> Parser (Referenced a) Source #
Orphan instances
(Eq a, Hashable a) => SwaggerMonoid (InsOrdHashSet a) Source # | |
Methods swaggerMempty :: InsOrdHashSet a Source # swaggerMappend :: InsOrdHashSet a -> InsOrdHashSet a -> InsOrdHashSet a Source # |