Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 :: Definitions SecurityScheme
- _swaggerSecurity :: [SecurityRequirement]
- _swaggerTags :: Set 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 :: Set 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 :: 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 {}
- 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
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.
Swagger | |
|
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.
Info | |
|
Instances
Contact information for the exposed API.
Contact | |
|
Instances
License information for the exposed API.
License | |
|
Instances
Eq License Source # | |
Data License Source # | |
Defined in Data.Swagger.Internal 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 fromString :: String -> License # | |
Generic License Source # | |
ToJSON License Source # | |
Defined in Data.Swagger.Internal | |
FromJSON License Source # | |
HasName License Text Source # | |
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.3.0.1-I2u1kttS1Fn4ceyOpeAUsE" 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 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 fromString :: String -> Host # | |
Generic Host Source # | |
ToJSON Host Source # | |
Defined in Data.Swagger.Internal | |
FromJSON Host Source # | |
HasName Host HostName Source # | |
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.3.0.1-I2u1kttS1Fn4ceyOpeAUsE" 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 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 # | |
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.3.0.1-I2u1kttS1Fn4ceyOpeAUsE" False) ((C1 (MetaCons "Http" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Https" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Ws" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Wss" PrefixI False) (U1 :: * -> *))) |
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
PathItem | |
|
Instances
Describes a single API operation on a path.
Operation | |
|
Instances
MimeList | |
|
Instances
Describes a single operation parameter. A unique parameter is defined by a combination of a name and location.
Param | |
|
Instances
data ParamAnySchema Source #
Instances
data ParamOtherSchema Source #
ParamOtherSchema | |
|
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
Instances
data SwaggerKind t Source #
Type used as a kind to avoid overlapping instances.
type family SwaggerKindType (k :: SwaggerKind *) :: * Source #
Instances
type SwaggerKindType (SwaggerKindParamOtherSchema :: SwaggerKind *) Source # | |
Defined in Data.Swagger.Internal | |
type SwaggerKindType (SwaggerKindSchema :: SwaggerKind *) Source # | |
Defined in Data.Swagger.Internal | |
type SwaggerKindType (SwaggerKindNormal t) Source # | |
Defined in Data.Swagger.Internal |
data SwaggerType t where Source #
Instances
swaggerTypeConstr :: Data (SwaggerType t) => SwaggerType t -> Constr Source #
swaggerTypeDataType :: SwaggerType t -> DataType Source #
swaggerCommonTypes :: [SwaggerType k] Source #
swaggerTypeConstrs :: [Constr] Source #
data ParamLocation Source #
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.
Instances
Instances
data NamedSchema Source #
A
with an optional name.
This name can be used in references.Schema
Instances
data ParamSchema (t :: SwaggerKind *) Source #
ParamSchema | |
|
Instances
Xml | |
|
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.
Responses | |
|
Instances
Eq Responses Source # | |
Data Responses Source # | |
Defined in Data.Swagger.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Responses -> c Responses # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Responses # toConstr :: Responses -> Constr # dataTypeOf :: Responses -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Responses) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses) # gmapT :: (forall b. Data b => b -> b) -> Responses -> Responses # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Responses -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Responses -> r # gmapQ :: (forall d. Data d => d -> u) -> Responses -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Responses -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Responses -> m Responses # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Responses -> m Responses # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Responses -> m Responses # | |
Show Responses Source # | |
Generic Responses Source # | |
Semigroup Responses Source # | |
Monoid Responses Source # | |
ToJSON Responses Source # | |
Defined in Data.Swagger.Internal |