| Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> | 
|---|---|
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Swagger
Contents
Description
Swagger™ is a project used to describe and document RESTful APIs.
The Swagger specification defines a set of files required to describe such an API. These files can then be used by the Swagger-UI project to display the API and Swagger-Codegen to generate clients in various languages. Additional utilities can also take advantage of the resulting files, such as testing tools.
Synopsis
- module Data.Swagger.Lens
- module Data.Swagger.Operation
- module Data.Swagger.ParamSchema
- module Data.Swagger.Schema
- module Data.Swagger.Schema.Validation
- 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 Host = Host {}
- data Scheme
- data Info = Info {}
- data Contact = Contact {}
- data License = License {- _licenseName :: Text
- _licenseUrl :: Maybe URL
 
- 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]
 
- data Tag = Tag {}
- type TagName = Text
- data SwaggerType t where
- type Format = Text
- type Definitions = InsOrdHashMap Text
- data CollectionFormat t where
- data Param = Param {}
- data ParamAnySchema
- data ParamOtherSchema = ParamOtherSchema {}
- data ParamLocation
- type ParamName = Text
- data Header = Header {}
- type HeaderName = Text
- data Example = Example {}
- 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 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 {}
- data SwaggerItems t where
- data Xml = Xml {- _xmlName :: Maybe Text
- _xmlNamespace :: Maybe Text
- _xmlPrefix :: Maybe Text
- _xmlAttribute :: Maybe Bool
- _xmlWrapped :: Maybe Bool
 
- type Pattern = Text
- data AdditionalProperties
- data Responses = Responses {}
- data Response = Response {}
- type HttpStatusCode = Int
- data SecurityScheme = SecurityScheme {}
- data SecuritySchemeType
- newtype SecurityRequirement = SecurityRequirement {}
- data ApiKeyParams = ApiKeyParams {}
- data ApiKeyLocation
- data OAuth2Params = OAuth2Params {}
- data OAuth2Flow
- type AuthorizationURL = Text
- type TokenURL = Text
- data ExternalDocs = ExternalDocs {}
- newtype Reference = Reference {- getReference :: Text
 
- data Referenced a
- newtype MimeList = MimeList {- getMimeList :: [MediaType]
 
- newtype URL = URL {}
How to use this library
This section explains how to use this library to work with Swagger specification.
Monoid
MonoidVirtually all types representing Swagger specification have MonoidMonoidmemptymappend
In this library you can use mempty
>>>encode (mempty :: Swagger)"{\"swagger\":\"2.0\",\"info\":{\"version\":\"\",\"title\":\"\"}}"
As you can see some spec properties (e.g. "version") are there even when the spec is empty.
 That is because these properties are actually required ones.
You should always override the default (empty) value for these properties, although it is not strictly necessary:
>>>encode mempty { _infoTitle = "Todo API", _infoVersion = "1.0" }"{\"version\":\"1.0\",\"title\":\"Todo API\"}"
You can merge two values using mappend(:<>)
>>>encode $ mempty { _infoTitle = "Todo API" } <> mempty { _infoVersion = "1.0" }"{\"version\":\"1.0\",\"title\":\"Todo API\"}"
This can be useful for combining specifications of endpoints into a whole API specification:
-- /account subAPI specification accountAPI :: Swagger -- /task subAPI specification taskAPI :: Swagger -- while API specification is just a combination -- of subAPIs' specifications api :: Swagger api = accountAPI <> taskAPI
Lenses and prisms
Since SwaggerMonoid
>>>:{encode $ (mempty :: Swagger) & definitions .~ [ ("User", mempty & type_ .~ SwaggerString) ] & paths .~ [ ("/user", mempty & get ?~ (mempty & produces ?~ MimeList ["application/json"] & at 200 ?~ ("OK" & _Inline.schema ?~ Ref (Reference "User")) & at 404 ?~ "User info not found")) ] :} "{\"swagger\":\"2.0\",\"info\":{\"version\":\"\",\"title\":\"\"},\"paths\":{\"/user\":{\"get\":{\"produces\":[\"application/json\"],\"responses\":{\"404\":{\"description\":\"User info not found\"},\"200\":{\"schema\":{\"$ref\":\"#/definitions/User\"},\"description\":\"OK\"}}}}},\"definitions\":{\"User\":{\"type\":\"string\"}}}"
In the snippet above we declare an API with a single path /user. This path provides method GET
 which produces application/json output. It should respond with code 200 and body specified
 by schema User which is defined in definitions404 meaning that user info is not found.
For convenience, swagger2 uses classy field lenses. It means that
 field accessor names can be overloaded for different types. One such
 common field is description
>>>encode $ (mempty :: Response) & description .~ "No content""{\"description\":\"No content\"}">>>:{encode $ (mempty :: Schema) & type_ .~ SwaggerBoolean & description ?~ "To be or not to be" :} "{\"description\":\"To be or not to be\",\"type\":\"boolean\"}"
ParamSchemaHasParamSchemaParamSchematype_SwaggerTypeHeaderparamSchema
>>>encode $ (mempty :: Header) & type_ .~ SwaggerNumber"{\"type\":\"number\"}"
Additionally, to simplify working with ResponseOperationResponsesat code
>>>:{encode $ (mempty :: Operation) & at 404 ?~ "Not found" :} "{\"responses\":{\"404\":{\"description\":\"Not found\"}}}"
You might've noticed that type_descriptiontype is a keyword in Haskell.
 A few other field accessors are modified in this way:
Schema specification
ParamSchemaSchema
ParamSchema tt parameter imposes some restrictions on type and items properties (see SwaggerTypeSwaggerItems
SchemaParamSchema
In most cases you will have a Haskell data type for which you would like to
 define a corresponding schema. To facilitate this use case
 swagger2 provides two classes for schema encoding.
 Both these classes provide means to encode types as Swagger schemas.
ToParamSchemaToHttpApiDatahttp-api-data package).
ToSchemaToJSONaeson package).
While lenses and prisms make it easy to define schemas, it might be that you don't need to:
 ToSchemaToParamSchemaGeneric
ToSchemaToJSONToJSONdefaultTaggedObjectToSchemaObjectWithSingleFielddefaultTaggedObject
Here's an example showing ToJSONToSchema
>>>data Person = Person { name :: String, age :: Integer } deriving Generic>>>instance ToJSON Person>>>instance ToSchema Person>>>encode (Person "David" 28)"{\"age\":28,\"name\":\"David\"}">>>encode $ toSchema (Proxy :: Proxy Person)"{\"required\":[\"name\",\"age\"],\"properties\":{\"name\":{\"type\":\"string\"},\"age\":{\"type\":\"integer\"}},\"type\":\"object\"}"
Please note that not all valid Haskell data types will have a proper swagger schema. For example while we can derive a schema for basic enums like
>>>data SampleEnum = ChoiceOne | ChoiceTwo deriving Generic>>>instance ToSchema SampleEnum>>>instance ToJSON SampleEnum
and for sum types that have constructors with values
>>>data SampleSumType = ChoiceInt Int | ChoiceString String deriving Generic>>>instance ToSchema SampleSumType>>>instance ToJSON SampleSumType
we can not derive a valid schema for a mix of the above. The following will result in a type error
Manipulation
Sometimes you have to work with an imported or generated SwaggerSwagger
Lenses and prisms can be used to manipulate such specification to add additional information, tags, extra responses, etc.
 To facilitate common needs, Data.Swagger.Operation module provides useful helpers.
Validation
While ToParamSchemaToSchemaToHttpApiDataToJSON
Data.Swagger.Schema.Validation addresses ToJSONToSchema
Re-exports
module Data.Swagger.Lens
module Data.Swagger.Operation
module Data.Swagger.ParamSchema
module Data.Swagger.Schema
Swagger specification
This is the root document object for the API specification.
Constructors
| Swagger | |
| Fields 
 | |
Instances
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 # | |
| 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.1.1-HnOoc3Duc6IA7Ce1Ri8TAc" 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)))) | |
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 # | |
| 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.1.1-HnOoc3Duc6IA7Ce1Ri8TAc" 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))) | |
Info types
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 :: (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 # | |
| 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.1.1-HnOoc3Duc6IA7Ce1Ri8TAc" 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)))) | |
PathItem
Describes the operations available on a single path.
 A PathItem
Constructors
| PathItem | |
| Fields 
 | |
Instances
Operations
Describes a single API operation on a path.
Constructors
| Operation | |
| 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 # | |
| ToJSON Tag Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Tag Source # | |
| HasName Tag TagName Source # | |
| HasTags Swagger (Set 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.3.1.1-HnOoc3Duc6IA7Ce1Ri8TAc" 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))))) | |
Types and formats
data SwaggerType t where Source #
Constructors
Instances
type Definitions = InsOrdHashMap Text Source #
A list of definitions that can be used in references.
data CollectionFormat t where Source #
Determines the format of the array.
Constructors
Instances
Parameters
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 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
Constructors
| Header | |
| Fields 
 | |
Instances
type HeaderName = Text Source #
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 # | |
| 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 | |
Schemas
data ParamSchema (t :: SwaggerKind *) Source #
Constructors
| ParamSchema | |
| Fields 
 | |
Instances
Constructors
Instances
data NamedSchema Source #
A Schema
Constructors
| NamedSchema | |
| 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
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 # | |
| ToJSON Xml Source # | |
| Defined in Data.Swagger.Internal | |
| 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 # | |
| Defined in Data.Swagger.Internal type Rep Xml = D1 (MetaData "Xml" "Data.Swagger.Internal" "swagger2-2.3.1.1-HnOoc3Duc6IA7Ce1Ri8TAc" 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)))))) | |
data AdditionalProperties Source #
Instances
Responses
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
Describes a single response from an API Operation.
Constructors
| Response | |
| Fields 
 | |
Instances
type HttpStatusCode = Int Source #
Security
data SecurityScheme Source #
Constructors
| SecurityScheme | |
| Fields 
 | |
Instances
data SecuritySchemeType Source #
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
API key
data ApiKeyParams Source #
Constructors
| ApiKeyParams | |
| Fields 
 | |
Instances
data ApiKeyLocation Source #
The location of the API key.
Constructors
| ApiKeyQuery | |
| ApiKeyHeader | 
Instances
OAuth2
data OAuth2Params Source #
Constructors
| OAuth2Params | |
| Fields 
 | |
Instances
data OAuth2Flow Source #
Constructors
| OAuth2Implicit AuthorizationURL | |
| OAuth2Password TokenURL | |
| OAuth2Application TokenURL | |
| OAuth2AccessCode AuthorizationURL TokenURL | 
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.
External documentation
data ExternalDocs Source #
Allows referencing an external resource for extended documentation.
Constructors
| ExternalDocs | |
| Fields 
 | |
Instances
References
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 # | |
| ToJSON Reference Source # | |
| Defined in Data.Swagger.Internal | |
| FromJSON Reference Source # | |
data Referenced a Source #
Instances
Miscellaneous
Constructors
| MimeList | |
| Fields 
 | |
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 # | |
| 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 # | |