| 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 {}
- type HttpStatusCode = Int
- data Response = Response {}
- type HeaderName = Text
- data Header = Header {}
- data Example = Example {}
- exampleConstr :: Constr
- exampleDataType :: DataType
- data ApiKeyLocation
- data ApiKeyParams = ApiKeyParams {}
- type AuthorizationURL = Text
- type TokenURL = Text
- data OAuth2Flow
- data OAuth2Params = OAuth2Params {}
- data SecuritySchemeType
- data SecurityScheme = SecurityScheme {}
- mergeSecurityScheme :: SecurityScheme -> 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
- 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
Contact information for the exposed API.
Constructors
| Contact | |
| Fields 
 | |
Instances
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 :: 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 # | |
| Show License Source # | |
| IsString License Source # | |
| Defined in Data.Swagger.Internal Methods fromString :: String -> License # | |
| Generic License Source # | |
| ToJSON License Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON License Source # | |
| HasName License Text Source # | |
| (k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "name" k License License a b Source # | |
| Defined in Data.Swagger.Optics | |
| (k ~ A_Lens, a ~ Maybe URL, b ~ Maybe URL) => LabelOptic "url" k License License a b Source # | |
| Defined in Data.Swagger.Optics | |
| 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.7-6mtrQuWhrGh4VV6RfcIgND" '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 :: forall r r'. (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 # | |
| ToJSON Host Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Host Source # | |
| HasName Host HostName Source # | |
| (k ~ A_Lens, a ~ HostName, b ~ HostName) => LabelOptic "name" k Host Host a b Source # | |
| Defined in Data.Swagger.Optics | |
| (k ~ A_Lens, a ~ Maybe PortNumber, b ~ Maybe PortNumber) => LabelOptic "port" k Host Host a b Source # | |
| Defined in Data.Swagger.Optics | |
| HasHost Swagger (Maybe Host) Source # | |
| HasPort Host (Maybe PortNumber) Source # | |
| Defined in Data.Swagger.Lens | |
| type Rep Host Source # | |
| Defined in Data.Swagger.Internal type Rep Host = D1 ('MetaData "Host" "Data.Swagger.Internal" "swagger2-2.7-6mtrQuWhrGh4VV6RfcIgND" '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 :: forall r r'. (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 # | |
| ToJSON Scheme Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Scheme Source # | |
| 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.7-6mtrQuWhrGh4VV6RfcIgND" '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 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
data ParamAnySchema Source #
Constructors
| ParamBody (Referenced Schema) | |
| ParamOther ParamOtherSchema | 
Instances
data ParamOtherSchema Source #
Constructors
| ParamOtherSchema | |
| Fields 
 | |
Instances
data SwaggerItems t where Source #
Items for SwaggerArray
SwaggerItemsPrimitiveCollectionFormat tfmt in SwaggerItemsPrimitive fmt schemaschema.
 This is different from the original Swagger's Items Object.
SwaggerItemsObjectSchema
SwaggerItemsArraySchema
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
Instances
data NamedSchema Source #
A Schema
Constructors
| NamedSchema | |
| Fields | |
Instances
data ParamSchema (t :: SwaggerKind *) Source #
Constructors
| ParamSchema | |
| 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
type HeaderName = Text Source #
Constructors
| Header | |
| Fields 
 | |
Instances
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 :: forall r r'. (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 # | |
| ToJSON Example Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Example Source # | |
| 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
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 :: 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 # | |
| Ord Tag Source # | |
| Show Tag Source # | |
| IsString Tag Source # | |
| Defined in Data.Swagger.Internal Methods fromString :: String -> Tag # | |
| Generic Tag Source # | |
| Hashable Tag Source # | |
| Defined in Data.Swagger.Internal | |
| ToJSON Tag Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Tag Source # | |
| HasName Tag TagName Source # | |
| (k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "description" k Tag Tag a b Source # | |
| Defined in Data.Swagger.Optics | |
| (k ~ A_Lens, a ~ Maybe ExternalDocs, b ~ Maybe ExternalDocs) => LabelOptic "externalDocs" k Tag Tag a b Source # | |
| Defined in Data.Swagger.Optics | |
| (k ~ A_Lens, a ~ TagName, b ~ TagName) => LabelOptic "name" k Tag Tag a b Source # | |
| Defined in Data.Swagger.Optics | |
| HasTags Swagger (InsOrdHashSet Tag) Source # | |
| Defined in Data.Swagger.Lens | |
| 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.7-6mtrQuWhrGh4VV6RfcIgND" '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 :: 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 # | |
| ToJSON Reference Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Reference Source # | |
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 :: 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 # | |
| Ord URL Source # | |
| Show URL Source # | |
| Hashable URL Source # | |
| Defined in Data.Swagger.Internal | |
| ToJSON URL Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON URL Source # | |
| SwaggerMonoid URL Source # | |
| Defined in Data.Swagger.Internal | |
| HasUrl ExternalDocs URL Source # | |
| Defined in Data.Swagger.Lens | |
| 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 # | |