Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Swagger.Internal
- 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 [Schema]
- _schemaProperties :: InsOrdHashMap Text (Referenced Schema)
- _schemaAdditionalProperties :: Maybe (Referenced Schema)
- _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 = 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 {}
- 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.
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
The host (name or ip) serving the API. It MAY include a port.
hostConstr :: Constr Source #
The transfer protocol of the API.
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
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
HasParamSchema s (ParamSchema t) => HasItems s (Maybe (SwaggerItems t)) Source # | |
Eq (SwaggerItems t) Source # | |
Data t => Data (SwaggerItems (SwaggerKindNormal * t)) Source # | |
Data (SwaggerItems (SwaggerKindParamOtherSchema *)) Source # | |
Data (SwaggerItems (SwaggerKindSchema *)) Source # | |
Show (SwaggerItems t) Source # | |
ToJSON (ParamSchema t) => ToJSON (SwaggerItems t) Source # | |
(FromJSON (CollectionFormat (SwaggerKindNormal * t)), FromJSON (ParamSchema (SwaggerKindNormal * t))) => FromJSON (SwaggerItems (SwaggerKindNormal * t)) Source # | |
FromJSON (SwaggerItems (SwaggerKindParamOtherSchema *)) Source # | |
FromJSON (SwaggerItems (SwaggerKindSchema *)) Source # | |
HasItems (ParamSchema t0) (Maybe (SwaggerItems t0)) Source # | |
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 *) Source # | |
type SwaggerKindType (SwaggerKindSchema *) Source # | |
type SwaggerKindType (SwaggerKindNormal * t) Source # | |
data SwaggerType t where Source #
Constructors
Instances
HasType Header (SwaggerType (SwaggerKindNormal * Header)) Source # | |
HasType NamedSchema (SwaggerType (SwaggerKindSchema *)) Source # | |
HasType Schema (SwaggerType (SwaggerKindSchema *)) Source # | |
HasType ParamOtherSchema (SwaggerType (SwaggerKindParamOtherSchema *)) Source # | |
Eq (SwaggerType t) Source # | |
Typeable * t => Data (SwaggerType (SwaggerKindNormal * t)) Source # | |
Data (SwaggerType (SwaggerKindParamOtherSchema *)) Source # | |
Data (SwaggerType (SwaggerKindSchema *)) Source # | |
Show (SwaggerType t) Source # | |
ToJSON (SwaggerType t) Source # | |
FromJSON (SwaggerType (SwaggerKindNormal * t)) Source # | |
FromJSON (SwaggerType (SwaggerKindParamOtherSchema *)) Source # | |
FromJSON (SwaggerType (SwaggerKindSchema *)) Source # | |
AesonDefaultValue (SwaggerType a) Source # | |
SwaggerMonoid (SwaggerType t) Source # | |
HasType (ParamSchema t0) (SwaggerType t0) Source # | |
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
with an optional name.
This name can be used in references.Schema
Constructors
NamedSchema | |
Fields |
Instances
data ParamSchema t Source #
Constructors
ParamSchema | |
Fields
|
Instances
Constructors
Xml | |
Fields
|
Instances
Eq Xml Source # | |
Data Xml Source # | |
Show Xml Source # | |
Generic Xml Source # | |
ToJSON Xml Source # | |
FromJSON Xml Source # | |
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 # | |
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 |
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 #
data OAuth2Params Source #
Constructors
OAuth2Params | |
Fields
|
Instances
data SecuritySchemeType Source #
Instances
data SecurityScheme Source #
Constructors
SecurityScheme | |
Fields
|
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 # | |
Ord Tag Source # | |
Show Tag Source # | |
IsString Tag Source # | |
Generic Tag Source # | |
ToJSON Tag Source # | |
FromJSON Tag Source # | |
HasName Tag TagName Source # | |
HasTags Swagger (Set Tag) Source # | |
HasExternalDocs Tag (Maybe ExternalDocs) Source # | |
HasDescription Tag (Maybe Text) Source # | |
type Rep Tag Source # | |
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
|
data Referenced a Source #
Instances
Functor Referenced Source # | |
HasParameters Operation [Referenced Param] Source # | |
HasParameters PathItem [Referenced Param] Source # | |
HasSchema Response (Maybe (Referenced Schema)) Source # | |
HasAdditionalProperties Schema (Maybe (Referenced Schema)) Source # | |
HasDefault Responses (Maybe (Referenced Response)) Source # | |
HasResponses Responses (InsOrdHashMap HttpStatusCode (Referenced Response)) Source # | |
HasProperties Schema (InsOrdHashMap Text (Referenced Schema)) Source # | |
Eq a => Eq (Referenced a) Source # | |
Data a => Data (Referenced a) Source # | |
Show a => Show (Referenced a) Source # | |
IsString a => IsString (Referenced a) Source # | |
ToJSON (Referenced Response) Source # | |
ToJSON (Referenced Schema) Source # | |
ToJSON (Referenced Param) Source # | |
FromJSON (Referenced Response) Source # | |
FromJSON (Referenced Schema) Source # | |
FromJSON (Referenced Param) Source # | |
Monoid a => SwaggerMonoid (Referenced a) Source # | |
referencedToJSON :: ToJSON a => Text -> Referenced a -> Value Source #
referencedParseJSON :: FromJSON a => Text -> Value -> Parser (Referenced a) Source #