swagger2-2.1.4.1: Swagger 2.0 data model

MaintainerNickolay Kudasov <nickolay@getshoptv.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

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

How to use this library

This section explains how to use this library to work with Swagger specification.

Monoid instances

Virtually all types representing Swagger specification have Monoid instances. The Monoid type class provides two methods — mempty and mappend.

In this library you can use mempty for a default/empty value. For instance:

>>> 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 or its infix version (<>):

>>> 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 Swagger has a fairly complex structure, lenses and prisms are used to work comfortably with it. In combination with Monoid instances, lenses make it fairly simple to construct/modify any part of the specification:

>>> :{
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 definitions property of swagger specification. Alternatively it may respond with code 404 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. Many components of a Swagger specification can have descriptions, and you can use the same name for them:

>>> 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\"}"

ParamSchema is basically the base schema specification and many types contain it (see HasParamSchema). So for convenience, all ParamSchema fields are transitively made fields of the type that has it. For example, you can use type_ to access SwaggerType of Header schema without having to use paramSchema:

>>> encode $ (mempty :: Header) & type_ .~ SwaggerNumber
"{\"type\":\"number\"}"

Additionally, to simplify working with Response, both Operation and Responses have direct access to it via at code. Example:

>>> :{
encode $ (mempty :: Operation)
  & at 404 ?~ "Not found"
:}
"{\"responses\":{\"404\":{\"description\":\"Not found\"}}}"

You might've noticed that type_ has an extra underscore in its name compared to, say, description field accessor. This is because type is a keyword in Haskell. A few other field accessors are modified in this way:

Schema specification

ParamSchema and Schema are the two core types for data model specification.

ParamSchema t specifies all the common properties, available for every data schema. The t parameter imposes some restrictions on type and items properties (see SwaggerType and SwaggerItems).

Schema is used for request and response bodies and allows specifying objects with properties in addition to what ParamSchema provides.

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.

ToParamSchema is intended to be used for primitive API endpoint parameters, such as query parameters, headers and URL path pieces. Its corresponding value-encoding class is ToHttpApiData (from http-api-data package).

ToSchema is used for request and response bodies and mostly differ from primitive parameters by allowing objects/mappings in addition to primitive types and arrays. Its corresponding value-encoding class is ToJSON (from aeson package).

While lenses and prisms make it easy to define schemas, it might be that you don't need to: ToSchema and ToParamSchema classes both have default Generic-based implementations!

ToSchema default implementation is also aligned with ToJSON default implementation with the only difference being for sum encoding. ToJSON defaults sum encoding to defaultTaggedObject, while ToSchema defaults to something which corresponds to ObjectWithSingleField. This is due to defaultTaggedObject behavior being hard to specify in Swagger.

Here's an example showing ToJSONToSchema correspondance:

>>> 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 bad schema

>>> data BadMixedType = ChoiceBool Bool | JustTag deriving Generic
>>> instance ToSchema BadMixedType
>>> instance ToJSON BadMixedType

This is due to the fact that ToJSON encodes empty constructors with an empty list which can not be described in a swagger schema.

Manipulation

Sometimes you have to work with an imported or generated Swagger. For instance, http://hackage.haskell.org/package/servant-swagger generates basic Swagger for a type-level servant API.

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 ToParamSchema and ToSchema provide means to easily obtain schemas for Haskell types, there is no static mechanism to ensure those instances correspond to the ToHttpApiData or ToJSON instances.

Data.Swagger.Schema.Validation addresses ToJSON/ToSchema validation.

Re-exports

Swagger specification

data Swagger Source #

This is the root document object for the API specification.

Constructors

Swagger 

Fields

  • _swaggerInfo :: Info

    Provides metadata about the API. The metadata can be used by the clients if needed.

  • _swaggerHost :: Maybe Host

    The host (name or ip) serving the API. It MAY include a port. If the host is not included, the host serving the documentation is to be used (including the port).

  • _swaggerBasePath :: Maybe FilePath

    The base path on which the API is served, which is relative to the host. If it is not included, the API is served directly under the host. The value MUST start with a leading slash (/).

  • _swaggerSchemes :: Maybe [Scheme]

    The transfer protocol of the API. If the schemes is not included, the default scheme to be used is the one used to access the Swagger definition itself.

  • _swaggerConsumes :: MimeList

    A list of MIME types the APIs can consume. This is global to all APIs but can be overridden on specific API calls.

  • _swaggerProduces :: MimeList

    A list of MIME types the APIs can produce. This is global to all APIs but can be overridden on specific API calls.

  • _swaggerPaths :: InsOrdHashMap FilePath PathItem

    The available paths and operations for the API. Holds the relative paths to the individual endpoints. The path is appended to the basePath in order to construct the full URL.

  • _swaggerDefinitions :: Definitions Schema

    An object to hold data types produced and consumed by operations.

  • _swaggerParameters :: Definitions Param

    An object to hold parameters that can be used across operations. This property does not define global parameters for all operations.

  • _swaggerResponses :: Definitions Response

    An object to hold responses that can be used across operations. This property does not define global responses for all operations.

  • _swaggerSecurityDefinitions :: Definitions SecurityScheme

    Security scheme definitions that can be used across the specification.

  • _swaggerSecurity :: [SecurityRequirement]

    A declaration of which security schemes are applied for the API as a whole. The list of values describes alternative security schemes that can be used (that is, there is a logical OR between the security requirements). Individual operations can override this definition.

  • _swaggerTags :: Set Tag

    A list of tags used by the specification with additional metadata. The order of the tags can be used to reflect on their order by the parsing tools. Not all tags that are used by the Operation Object must be declared. The tags that are not declared may be organized randomly or based on the tools' logic. Each tag name in the list MUST be unique.

  • _swaggerExternalDocs :: Maybe ExternalDocs

    Additional external documentation.

Instances

Eq Swagger Source # 

Methods

(==) :: Swagger -> Swagger -> Bool #

(/=) :: Swagger -> Swagger -> Bool #

Data Swagger Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Swagger -> c Swagger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Swagger #

toConstr :: Swagger -> Constr #

dataTypeOf :: Swagger -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Swagger) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Swagger) #

gmapT :: (forall b. Data b => b -> b) -> Swagger -> Swagger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Swagger -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Swagger -> r #

gmapQ :: (forall d. Data d => d -> u) -> Swagger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Swagger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Swagger -> m Swagger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Swagger -> m Swagger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Swagger -> m Swagger #

Show Swagger Source # 
Generic Swagger Source # 

Associated Types

type Rep Swagger :: * -> * #

Methods

from :: Swagger -> Rep Swagger x #

to :: Rep Swagger x -> Swagger #

Monoid Swagger Source # 
ToJSON Swagger Source # 
FromJSON Swagger Source # 
Generic Swagger Source # 

Associated Types

type Code Swagger :: [[*]] #

HasDatatypeInfo Swagger Source # 
HasSwaggerAesonOptions Swagger Source # 
HasProduces Swagger MimeList Source # 
HasInfo Swagger Info Source # 
HasConsumes Swagger MimeList Source # 
HasTags Swagger (Set Tag) Source # 
HasSecurityDefinitions Swagger (Definitions SecurityScheme) Source # 
HasSecurity Swagger [SecurityRequirement] Source # 
HasSchemes Swagger (Maybe [Scheme]) Source # 
HasResponses Swagger (Definitions Response) Source # 
HasParameters Swagger (Definitions Param) Source # 
HasHost Swagger (Maybe Host) Source # 
HasExternalDocs Swagger (Maybe ExternalDocs) Source # 
HasDefinitions Swagger (Definitions Schema) Source # 
HasBasePath Swagger (Maybe FilePath) Source # 
HasPaths Swagger (InsOrdHashMap FilePath PathItem) Source # 
type Rep Swagger Source # 
type Rep Swagger = D1 (MetaData "Swagger" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Swagger" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Info)) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Host))) (S1 (MetaSel (Just Symbol "_swaggerBasePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerSchemes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Scheme]))) (S1 (MetaSel (Just Symbol "_swaggerConsumes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MimeList))) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerProduces") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MimeList)) (S1 (MetaSel (Just Symbol "_swaggerPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap FilePath PathItem)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerDefinitions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Definitions Schema))) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerParameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Definitions Param))) (S1 (MetaSel (Just Symbol "_swaggerResponses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Definitions Response))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerSecurityDefinitions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Definitions SecurityScheme))) (S1 (MetaSel (Just Symbol "_swaggerSecurity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SecurityRequirement]))) ((:*:) (S1 (MetaSel (Just Symbol "_swaggerTags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Tag))) (S1 (MetaSel (Just Symbol "_swaggerExternalDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalDocs))))))))
type Code Swagger Source # 
type Code Swagger = (:) [*] ((:) * Info ((:) * (Maybe Host) ((:) * (Maybe FilePath) ((:) * (Maybe [Scheme]) ((:) * MimeList ((:) * MimeList ((:) * (InsOrdHashMap FilePath PathItem) ((:) * (Definitions Schema) ((:) * (Definitions Param) ((:) * (Definitions Response) ((:) * (Definitions SecurityScheme) ((:) * [SecurityRequirement] ((:) * (Set Tag) ((:) * (Maybe ExternalDocs) ([] *))))))))))))))) ([] [*])

data Host Source #

The host (name or ip) serving the API. It MAY include a port.

Constructors

Host 

Fields

Instances

Eq Host Source # 

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

Data Host Source # 

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 #

toConstr :: Host -> Constr #

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 # 

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

IsString Host Source # 

Methods

fromString :: String -> Host #

Generic Host Source # 

Associated Types

type Rep Host :: * -> * #

Methods

from :: Host -> Rep Host x #

to :: Rep Host x -> Host #

ToJSON Host Source # 
FromJSON Host Source # 
HasName Host HostName Source # 
HasHost Swagger (Maybe Host) Source # 
HasPort Host (Maybe PortNumber) Source # 
type Rep Host Source # 
type Rep Host = D1 (MetaData "Host" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Host" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_hostName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HostName)) (S1 (MetaSel (Just Symbol "_hostPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PortNumber)))))

data Scheme Source #

The transfer protocol of the API.

Constructors

Http 
Https 
Ws 
Wss 

Instances

Eq Scheme Source # 

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Data Scheme Source # 

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 # 

Associated Types

type Rep Scheme :: * -> * #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

ToJSON Scheme Source # 
FromJSON Scheme Source # 
HasSchemes Operation (Maybe [Scheme]) Source # 
HasSchemes Swagger (Maybe [Scheme]) Source # 
type Rep Scheme Source # 
type Rep Scheme = D1 (MetaData "Scheme" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" 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)))

Info types

data Info Source #

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 # 

Methods

(==) :: Info -> Info -> Bool #

(/=) :: Info -> Info -> Bool #

Data Info Source # 

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 #

toConstr :: Info -> Constr #

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 # 

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Generic Info Source # 

Associated Types

type Rep Info :: * -> * #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Monoid Info Source # 

Methods

mempty :: Info #

mappend :: Info -> Info -> Info #

mconcat :: [Info] -> Info #

ToJSON Info Source # 
FromJSON Info Source # 
SwaggerMonoid Info Source # 
AesonDefaultValue Info Source # 
HasInfo Swagger Info Source # 
HasVersion Info Text Source # 
HasTitle Info Text Source # 
HasTermsOfService Info (Maybe Text) Source # 
HasLicense Info (Maybe License) Source # 
HasDescription Info (Maybe Text) Source # 
HasContact Info (Maybe Contact) Source # 
type Rep Info Source # 

data Contact Source #

Contact information for the exposed API.

Constructors

Contact 

Fields

Instances

Eq Contact Source # 

Methods

(==) :: Contact -> Contact -> Bool #

(/=) :: Contact -> Contact -> Bool #

Data Contact Source # 

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 # 

Associated Types

type Rep Contact :: * -> * #

Methods

from :: Contact -> Rep Contact x #

to :: Rep Contact x -> Contact #

Monoid Contact Source # 
ToJSON Contact Source # 
FromJSON Contact Source # 
HasName Contact (Maybe Text) Source # 
HasContact Info (Maybe Contact) Source # 
HasUrl Contact (Maybe URL) Source # 
HasEmail Contact (Maybe Text) Source # 
type Rep Contact Source # 
type Rep Contact = D1 (MetaData "Contact" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Contact" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_contactName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_contactUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_contactEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))

data License Source #

License information for the exposed API.

Constructors

License 

Fields

Instances

Eq License Source # 

Methods

(==) :: License -> License -> Bool #

(/=) :: License -> License -> Bool #

Data License Source # 

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 # 

Methods

fromString :: String -> License #

Generic License Source # 

Associated Types

type Rep License :: * -> * #

Methods

from :: License -> Rep License x #

to :: Rep License x -> License #

ToJSON License Source # 
FromJSON License Source # 
HasName License Text Source # 
HasLicense Info (Maybe License) Source # 
HasUrl License (Maybe URL) Source # 
type Rep License Source # 
type Rep License = D1 (MetaData "License" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "License" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_licenseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_licenseUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URL)))))

PathItem

data PathItem Source #

Describes the operations available on a single path. A PathItem 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.

Constructors

PathItem 

Fields

Instances

Eq PathItem Source # 
Data PathItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PathItem -> c PathItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PathItem #

toConstr :: PathItem -> Constr #

dataTypeOf :: PathItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PathItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem) #

gmapT :: (forall b. Data b => b -> b) -> PathItem -> PathItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PathItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PathItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> PathItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PathItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PathItem -> m PathItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PathItem -> m PathItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PathItem -> m PathItem #

Show PathItem Source # 
Generic PathItem Source # 

Associated Types

type Rep PathItem :: * -> * #

Methods

from :: PathItem -> Rep PathItem x #

to :: Rep PathItem x -> PathItem #

Monoid PathItem Source # 
ToJSON PathItem Source # 
FromJSON PathItem Source # 
Generic PathItem Source # 

Associated Types

type Code PathItem :: [[*]] #

HasDatatypeInfo PathItem Source # 
SwaggerMonoid PathItem Source # 
HasSwaggerAesonOptions PathItem Source # 
HasParameters PathItem [Referenced Param] Source # 
HasPut PathItem (Maybe Operation) Source # 
HasPost PathItem (Maybe Operation) Source # 
HasPatch PathItem (Maybe Operation) Source # 
HasOptions PathItem (Maybe Operation) Source # 
HasHead PathItem (Maybe Operation) Source # 
HasGet PathItem (Maybe Operation) Source # 
HasDelete PathItem (Maybe Operation) Source # 
HasPaths Swagger (InsOrdHashMap FilePath PathItem) Source # 
SwaggerMonoid (InsOrdHashMap FilePath PathItem) Source # 
type Rep PathItem Source # 
type Code PathItem Source # 
type Code PathItem = (:) [*] ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * (Maybe Operation) ((:) * [Referenced Param] ([] *))))))))) ([] [*])

Operations

data Operation Source #

Describes a single API operation on a path.

Constructors

Operation 

Fields

  • _operationTags :: Set TagName

    A list of tags for API documentation control. Tags can be used for logical grouping of operations by resources or any other qualifier.

  • _operationSummary :: Maybe Text

    A short summary of what the operation does. For maximum readability in the swagger-ui, this field SHOULD be less than 120 characters.

  • _operationDescription :: Maybe Text

    A verbose explanation of the operation behavior. GFM syntax can be used for rich text representation.

  • _operationExternalDocs :: Maybe ExternalDocs

    Additional external documentation for this operation.

  • _operationOperationId :: Maybe Text

    Unique string used to identify the operation. The id MUST be unique among all operations described in the API. Tools and libraries MAY use the it to uniquely identify an operation, therefore, it is recommended to follow common programming naming conventions.

  • _operationConsumes :: Maybe MimeList

    A list of MIME types the operation can consume. This overrides the consumes. Just [] MAY be used to clear the global definition.

  • _operationProduces :: Maybe MimeList

    A list of MIME types the operation can produce. This overrides the produces. Just [] MAY be used to clear the global definition.

  • _operationParameters :: [Referenced Param]

    A list of parameters that are applicable for this operation. If a parameter is already defined at the PathItem, the new definition will override it, but can never remove it. The list MUST NOT include duplicated parameters. A unique parameter is defined by a combination of a name and location.

  • _operationResponses :: Responses

    The list of possible responses as they are returned from executing this operation.

  • _operationSchemes :: Maybe [Scheme]

    The transfer protocol for the operation. The value overrides schemes.

  • _operationDeprecated :: Maybe Bool

    Declares this operation to be deprecated. Usage of the declared operation should be refrained. Default value is False.

  • _operationSecurity :: [SecurityRequirement]

    A declaration of which security schemes are applied for this operation. The list of values describes alternative security schemes that can be used (that is, there is a logical OR between the security requirements). This definition overrides any declared top-level security. To remove a top-level security declaration, Just [] can be used.

Instances

Eq Operation Source # 
Data Operation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Operation -> c Operation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Operation #

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Operation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation) #

gmapT :: (forall b. Data b => b -> b) -> Operation -> Operation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Operation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Operation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Operation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Operation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Operation -> m Operation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Operation -> m Operation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Operation -> m Operation #

Show Operation Source # 
Generic Operation Source # 

Associated Types

type Rep Operation :: * -> * #

Monoid Operation Source # 
ToJSON Operation Source # 
FromJSON Operation Source # 
Generic Operation Source # 

Associated Types

type Code Operation :: [[*]] #

HasDatatypeInfo Operation Source # 
SwaggerMonoid Operation Source # 
HasSwaggerAesonOptions Operation Source # 
HasResponses Operation Responses Source # 
HasTags Operation (Set TagName) Source # 
HasSecurity Operation [SecurityRequirement] Source # 
HasSchemes Operation (Maybe [Scheme]) Source # 
HasProduces Operation (Maybe MimeList) Source # 
HasParameters Operation [Referenced Param] Source # 
HasExternalDocs Operation (Maybe ExternalDocs) Source # 
HasConsumes Operation (Maybe MimeList) Source # 
HasDescription Operation (Maybe Text) Source # 
HasPut PathItem (Maybe Operation) Source # 
HasPost PathItem (Maybe Operation) Source # 
HasPatch PathItem (Maybe Operation) Source # 
HasOptions PathItem (Maybe Operation) Source # 
HasHead PathItem (Maybe Operation) Source # 
HasGet PathItem (Maybe Operation) Source # 
HasDelete PathItem (Maybe Operation) Source # 
HasSummary Operation (Maybe Text) Source # 
HasOperationId Operation (Maybe Text) Source # 
HasDeprecated Operation (Maybe Bool) Source # 
type Rep Operation Source # 
type Rep Operation = D1 (MetaData "Operation" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Operation" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_operationTags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set TagName))) ((:*:) (S1 (MetaSel (Just Symbol "_operationSummary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_operationDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_operationExternalDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalDocs))) ((:*:) (S1 (MetaSel (Just Symbol "_operationOperationId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_operationConsumes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MimeList)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_operationProduces") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MimeList))) ((:*:) (S1 (MetaSel (Just Symbol "_operationParameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Referenced Param])) (S1 (MetaSel (Just Symbol "_operationResponses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Responses)))) ((:*:) (S1 (MetaSel (Just Symbol "_operationSchemes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Scheme]))) ((:*:) (S1 (MetaSel (Just Symbol "_operationDeprecated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_operationSecurity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SecurityRequirement])))))))
type Code Operation Source # 
type Code Operation = (:) [*] ((:) * (Set TagName) ((:) * (Maybe Text) ((:) * (Maybe Text) ((:) * (Maybe ExternalDocs) ((:) * (Maybe Text) ((:) * (Maybe MimeList) ((:) * (Maybe MimeList) ((:) * [Referenced Param] ((:) * Responses ((:) * (Maybe [Scheme]) ((:) * (Maybe Bool) ((:) * [SecurityRequirement] ([] *))))))))))))) ([] [*])
type Index Operation # 
type IxValue Operation # 

data Tag Source #

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 # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

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 #

toConstr :: Tag -> Constr #

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 # 

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

IsString Tag Source # 

Methods

fromString :: String -> Tag #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

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 # 
type Rep Tag = D1 (MetaData "Tag" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Tag" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TagName)) ((:*:) (S1 (MetaSel (Just Symbol "_tagDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tagExternalDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalDocs))))))

type TagName = Text Source #

Tag name.

Types and formats

data SwaggerType t where Source #

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 # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerType (SwaggerKindNormal * t) -> c (SwaggerType (SwaggerKindNormal * t)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerType (SwaggerKindNormal * t)) #

toConstr :: SwaggerType (SwaggerKindNormal * t) -> Constr #

dataTypeOf :: SwaggerType (SwaggerKindNormal * t) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerType (SwaggerKindNormal * t))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerType (SwaggerKindNormal * t))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerType (SwaggerKindNormal * t) -> SwaggerType (SwaggerKindNormal * t) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindNormal * t) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindNormal * t) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindNormal * t) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindNormal * t) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindNormal * t) -> m (SwaggerType (SwaggerKindNormal * t)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindNormal * t) -> m (SwaggerType (SwaggerKindNormal * t)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindNormal * t) -> m (SwaggerType (SwaggerKindNormal * t)) #

Data (SwaggerType (SwaggerKindParamOtherSchema *)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerType (SwaggerKindParamOtherSchema *) -> c (SwaggerType (SwaggerKindParamOtherSchema *)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerType (SwaggerKindParamOtherSchema *)) #

toConstr :: SwaggerType (SwaggerKindParamOtherSchema *) -> Constr #

dataTypeOf :: SwaggerType (SwaggerKindParamOtherSchema *) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerType (SwaggerKindParamOtherSchema *))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerType (SwaggerKindParamOtherSchema *))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerType (SwaggerKindParamOtherSchema *) -> SwaggerType (SwaggerKindParamOtherSchema *) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindParamOtherSchema *) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindParamOtherSchema *) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindParamOtherSchema *) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindParamOtherSchema *) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindParamOtherSchema *) -> m (SwaggerType (SwaggerKindParamOtherSchema *)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindParamOtherSchema *) -> m (SwaggerType (SwaggerKindParamOtherSchema *)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindParamOtherSchema *) -> m (SwaggerType (SwaggerKindParamOtherSchema *)) #

Data (SwaggerType (SwaggerKindSchema *)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerType (SwaggerKindSchema *) -> c (SwaggerType (SwaggerKindSchema *)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerType (SwaggerKindSchema *)) #

toConstr :: SwaggerType (SwaggerKindSchema *) -> Constr #

dataTypeOf :: SwaggerType (SwaggerKindSchema *) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerType (SwaggerKindSchema *))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerType (SwaggerKindSchema *))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerType (SwaggerKindSchema *) -> SwaggerType (SwaggerKindSchema *) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindSchema *) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerType (SwaggerKindSchema *) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindSchema *) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerType (SwaggerKindSchema *) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindSchema *) -> m (SwaggerType (SwaggerKindSchema *)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindSchema *) -> m (SwaggerType (SwaggerKindSchema *)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerType (SwaggerKindSchema *) -> m (SwaggerType (SwaggerKindSchema *)) #

Show (SwaggerType t) Source # 
ToJSON (SwaggerType t) Source # 
FromJSON (SwaggerType (SwaggerKindNormal * t)) Source # 
FromJSON (SwaggerType (SwaggerKindParamOtherSchema *)) Source # 
FromJSON (SwaggerType (SwaggerKindSchema *)) Source # 
SwaggerMonoid (SwaggerType t) Source # 
AesonDefaultValue (SwaggerType a) Source # 
HasType (ParamSchema t0) (SwaggerType t0) Source # 

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.

Instances

Eq (CollectionFormat t) Source # 
Data t => Data (CollectionFormat (SwaggerKindNormal * t)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CollectionFormat (SwaggerKindNormal * t) -> c (CollectionFormat (SwaggerKindNormal * t)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CollectionFormat (SwaggerKindNormal * t)) #

toConstr :: CollectionFormat (SwaggerKindNormal * t) -> Constr #

dataTypeOf :: CollectionFormat (SwaggerKindNormal * t) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CollectionFormat (SwaggerKindNormal * t))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CollectionFormat (SwaggerKindNormal * t))) #

gmapT :: (forall b. Data b => b -> b) -> CollectionFormat (SwaggerKindNormal * t) -> CollectionFormat (SwaggerKindNormal * t) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CollectionFormat (SwaggerKindNormal * t) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CollectionFormat (SwaggerKindNormal * t) -> r #

gmapQ :: (forall d. Data d => d -> u) -> CollectionFormat (SwaggerKindNormal * t) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CollectionFormat (SwaggerKindNormal * t) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindNormal * t) -> m (CollectionFormat (SwaggerKindNormal * t)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindNormal * t) -> m (CollectionFormat (SwaggerKindNormal * t)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindNormal * t) -> m (CollectionFormat (SwaggerKindNormal * t)) #

Data (CollectionFormat (SwaggerKindParamOtherSchema *)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> c (CollectionFormat (SwaggerKindParamOtherSchema *)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CollectionFormat (SwaggerKindParamOtherSchema *)) #

toConstr :: CollectionFormat (SwaggerKindParamOtherSchema *) -> Constr #

dataTypeOf :: CollectionFormat (SwaggerKindParamOtherSchema *) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CollectionFormat (SwaggerKindParamOtherSchema *))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CollectionFormat (SwaggerKindParamOtherSchema *))) #

gmapT :: (forall b. Data b => b -> b) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> CollectionFormat (SwaggerKindParamOtherSchema *) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CollectionFormat (SwaggerKindParamOtherSchema *) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CollectionFormat (SwaggerKindParamOtherSchema *) -> r #

gmapQ :: (forall d. Data d => d -> u) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> m (CollectionFormat (SwaggerKindParamOtherSchema *)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> m (CollectionFormat (SwaggerKindParamOtherSchema *)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CollectionFormat (SwaggerKindParamOtherSchema *) -> m (CollectionFormat (SwaggerKindParamOtherSchema *)) #

Show (CollectionFormat t) Source # 
ToJSON (CollectionFormat t) Source # 
FromJSON (CollectionFormat (SwaggerKindNormal * t)) Source # 
FromJSON (CollectionFormat (SwaggerKindParamOtherSchema *)) Source # 

Parameters

data Param Source #

Describes a single operation parameter. A unique parameter is defined by a combination of a name and location.

Constructors

Param 

Fields

  • _paramName :: Text

    The name of the parameter. Parameter names are case sensitive.

  • _paramDescription :: Maybe Text

    A brief description of the parameter. This could contain examples of use. GFM syntax can be used for rich text representation.

  • _paramRequired :: Maybe Bool

    Determines whether this parameter is mandatory. If the parameter is in "path", this property is required and its value MUST be true. Otherwise, the property MAY be included and its default value is False.

  • _paramSchema :: ParamAnySchema

    Parameter schema.

Instances

Eq Param Source # 

Methods

(==) :: Param -> Param -> Bool #

(/=) :: Param -> Param -> Bool #

Data Param Source # 

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 #

toConstr :: Param -> Constr #

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 # 

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

Generic Param Source # 

Associated Types

type Rep Param :: * -> * #

Methods

from :: Param -> Rep Param x #

to :: Rep Param x -> Param #

Monoid Param Source # 

Methods

mempty :: Param #

mappend :: Param -> Param -> Param #

mconcat :: [Param] -> Param #

ToJSON Param Source # 
FromJSON Param Source # 
Generic Param Source # 

Associated Types

type Code Param :: [[*]] #

Methods

from :: Param -> Rep Param #

to :: Rep Param -> Param #

HasDatatypeInfo Param Source # 

Methods

datatypeInfo :: proxy Param -> DatatypeInfo (Code Param) #

SwaggerMonoid Param Source # 
HasSwaggerAesonOptions Param Source # 
HasName Param Text Source # 
HasSchema Param ParamAnySchema Source # 
HasParameters Operation [Referenced Param] Source # 
HasParameters PathItem [Referenced Param] Source # 
HasParameters Swagger (Definitions Param) Source # 
HasDescription Param (Maybe Text) Source # 
HasRequired Param (Maybe Bool) Source # 
ToJSON (Referenced Param) Source # 
FromJSON (Referenced Param) Source # 
type Rep Param Source # 
type Code Param Source # 
type Code Param = (:) [*] ((:) * Text ((:) * (Maybe Text) ((:) * (Maybe Bool) ((:) * ParamAnySchema ([] *))))) ([] [*])

data ParamAnySchema Source #

Instances

Eq ParamAnySchema Source # 
Data ParamAnySchema Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParamAnySchema #

toConstr :: ParamAnySchema -> Constr #

dataTypeOf :: ParamAnySchema -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParamAnySchema) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParamAnySchema) #

gmapT :: (forall b. Data b => b -> b) -> ParamAnySchema -> ParamAnySchema #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamAnySchema -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamAnySchema -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamAnySchema -> m ParamAnySchema #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamAnySchema -> m ParamAnySchema #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamAnySchema -> m ParamAnySchema #

Show ParamAnySchema Source # 
Generic ParamAnySchema Source # 

Associated Types

type Rep ParamAnySchema :: * -> * #

ToJSON ParamAnySchema Source # 
FromJSON ParamAnySchema Source # 
SwaggerMonoid ParamAnySchema Source # 
AesonDefaultValue ParamAnySchema Source # 
HasSchema Param ParamAnySchema Source # 
type Rep ParamAnySchema Source # 
type Rep ParamAnySchema = D1 (MetaData "ParamAnySchema" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) ((:+:) (C1 (MetaCons "ParamBody" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Referenced Schema)))) (C1 (MetaCons "ParamOther" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParamOtherSchema))))

data ParamOtherSchema Source #

Constructors

ParamOtherSchema 

Fields

Instances

Eq ParamOtherSchema Source # 
Data ParamOtherSchema Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParamOtherSchema #

toConstr :: ParamOtherSchema -> Constr #

dataTypeOf :: ParamOtherSchema -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParamOtherSchema) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParamOtherSchema) #

gmapT :: (forall b. Data b => b -> b) -> ParamOtherSchema -> ParamOtherSchema #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamOtherSchema -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamOtherSchema -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamOtherSchema -> m ParamOtherSchema #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamOtherSchema -> m ParamOtherSchema #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamOtherSchema -> m ParamOtherSchema #

Show ParamOtherSchema Source # 
Generic ParamOtherSchema Source # 
Monoid ParamOtherSchema Source # 
ToJSON ParamOtherSchema Source # 
FromJSON ParamOtherSchema Source # 
Generic ParamOtherSchema Source # 
HasDatatypeInfo ParamOtherSchema Source # 
SwaggerMonoid ParamOtherSchema Source # 
HasSwaggerAesonOptions ParamOtherSchema Source # 
HasIn ParamOtherSchema ParamLocation Source # 
HasParamSchema ParamOtherSchema (ParamSchema (SwaggerKindParamOtherSchema Type)) Source # 
HasAllowEmptyValue ParamOtherSchema (Maybe Bool) Source # 
HasType ParamOtherSchema (SwaggerType (SwaggerKindParamOtherSchema *)) Source # 
HasDefault ParamOtherSchema (Maybe Value) Source # 
type Rep ParamOtherSchema Source # 
type Rep ParamOtherSchema = D1 (MetaData "ParamOtherSchema" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "ParamOtherSchema" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_paramOtherSchemaIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParamLocation)) ((:*:) (S1 (MetaSel (Just Symbol "_paramOtherSchemaAllowEmptyValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_paramOtherSchemaParamSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParamSchema (SwaggerKindParamOtherSchema *)))))))
type Code ParamOtherSchema Source # 
type Code ParamOtherSchema = (:) [*] ((:) * ParamLocation ((:) * (Maybe Bool) ((:) * (ParamSchema (SwaggerKindParamOtherSchema Type)) ([] *)))) ([] [*])

data ParamLocation Source #

Constructors

ParamQuery

Parameters that are appended to the URL. For example, in /items?id=###, the query parameter is id.

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 items{itemId}, the path parameter is itemId.

ParamFormData

Used to describe the payload of an HTTP request when either application/x-www-form-urlencoded or multipart/form-data are used as the content type of the request (in Swagger's definition, the consumes property of an operation). This is the only parameter type that can be used to send files, thus supporting the ParamFile type. Since form parameters are sent in the payload, they cannot be declared together with a body parameter for the same operation. Form parameters have a different format based on the content-type used (for further details, consult http://www.w3.org/TR/html401/interact/forms.html#h-17.13.4).

Instances

Eq ParamLocation Source # 
Data ParamLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamLocation -> c ParamLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParamLocation #

toConstr :: ParamLocation -> Constr #

dataTypeOf :: ParamLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParamLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParamLocation) #

gmapT :: (forall b. Data b => b -> b) -> ParamLocation -> ParamLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation #

Show ParamLocation Source # 
Generic ParamLocation Source # 

Associated Types

type Rep ParamLocation :: * -> * #

ToJSON ParamLocation Source # 
FromJSON ParamLocation Source # 
SwaggerMonoid ParamLocation Source # 
AesonDefaultValue ParamLocation Source # 
HasIn ParamOtherSchema ParamLocation Source # 
type Rep ParamLocation Source # 
type Rep ParamLocation = D1 (MetaData "ParamLocation" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) ((:+:) ((:+:) (C1 (MetaCons "ParamQuery" PrefixI False) U1) (C1 (MetaCons "ParamHeader" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ParamPath" PrefixI False) U1) (C1 (MetaCons "ParamFormData" PrefixI False) U1)))

data Header Source #

Constructors

Header 

Fields

Instances

Eq Header Source # 

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Data Header Source # 

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 # 

Associated Types

type Rep Header :: * -> * #

Methods

from :: Header -> Rep Header x #

to :: Rep Header x -> Header #

Monoid Header Source # 
ToJSON Header Source # 
FromJSON Header Source # 
Generic Header Source # 

Associated Types

type Code Header :: [[*]] #

Methods

from :: Header -> Rep Header #

to :: Rep Header -> Header #

HasDatatypeInfo Header Source # 
HasSwaggerAesonOptions Header Source # 
HasDescription Header (Maybe Text) Source # 
HasParamSchema Header (ParamSchema (SwaggerKindNormal * Header)) Source # 
HasType Header (SwaggerType (SwaggerKindNormal * Header)) Source # 
HasDefault Header (Maybe Value) Source # 
HasHeaders Response (InsOrdHashMap HeaderName Header) Source # 
type Rep Header Source # 
type Rep Header = D1 (MetaData "Header" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Header" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_headerDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_headerParamSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParamSchema (SwaggerKindNormal * Header))))))
type Code Header Source # 
type Code Header = (:) [*] ((:) * (Maybe Text) ((:) * (ParamSchema (SwaggerKindNormal * Header)) ([] *))) ([] [*])

data Example Source #

Constructors

Example 

Instances

Eq Example Source # 

Methods

(==) :: Example -> Example -> Bool #

(/=) :: Example -> Example -> Bool #

Data Example Source # 

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 # 

Associated Types

type Rep Example :: * -> * #

Methods

from :: Example -> Rep Example x #

to :: Rep Example x -> Example #

Monoid Example Source # 
ToJSON Example Source # 
FromJSON Example Source # 
HasExamples Response (Maybe Example) Source # 
type Rep Example Source # 
type Rep Example = D1 (MetaData "Example" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Example" PrefixI True) (S1 (MetaSel (Just Symbol "getExample") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map MediaType Value))))

Schemas

data ParamSchema t Source #

Constructors

ParamSchema 

Fields

Instances

HasParamSchema Header (ParamSchema (SwaggerKindNormal * Header)) Source # 
HasParamSchema NamedSchema (ParamSchema (SwaggerKindSchema *)) Source # 
HasParamSchema Schema (ParamSchema (SwaggerKindSchema Type)) Source # 
HasParamSchema ParamOtherSchema (ParamSchema (SwaggerKindParamOtherSchema Type)) Source # 
Eq (ParamSchema t) Source # 
(Typeable (SwaggerKind *) k, Data (SwaggerType k), Data (SwaggerItems k)) => Data (ParamSchema k) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamSchema k -> c (ParamSchema k) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParamSchema k) #

toConstr :: ParamSchema k -> Constr #

dataTypeOf :: ParamSchema k -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ParamSchema k)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParamSchema k)) #

gmapT :: (forall b. Data b => b -> b) -> ParamSchema k -> ParamSchema k #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamSchema k -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamSchema k -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamSchema k -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamSchema k -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamSchema k -> m (ParamSchema k) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSchema k -> m (ParamSchema k) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSchema k -> m (ParamSchema k) #

Show (ParamSchema t) Source # 
Generic (ParamSchema t) Source # 

Associated Types

type Rep (ParamSchema t) :: * -> * #

Methods

from :: ParamSchema t -> Rep (ParamSchema t) x #

to :: Rep (ParamSchema t) x -> ParamSchema t #

Monoid (ParamSchema t) Source # 
ToJSON (ParamSchema k) Source # 
(FromJSON (SwaggerType (SwaggerKindNormal * t)), FromJSON (SwaggerItems (SwaggerKindNormal * t))) => FromJSON (ParamSchema (SwaggerKindNormal * t)) Source # 
FromJSON (ParamSchema (SwaggerKindParamOtherSchema *)) Source # 
FromJSON (ParamSchema (SwaggerKindSchema *)) Source # 
Generic (ParamSchema t0) Source # 

Associated Types

type Code (ParamSchema t0) :: [[*]] #

Methods

from :: ParamSchema t0 -> Rep (ParamSchema t0) #

to :: Rep (ParamSchema t0) -> ParamSchema t0 #

HasDatatypeInfo (ParamSchema t0) Source # 

Methods

datatypeInfo :: proxy (ParamSchema t0) -> DatatypeInfo (Code (ParamSchema t0)) #

SwaggerMonoid (ParamSchema t) Source # 
AesonDefaultValue (ParamSchema s) Source # 
HasSwaggerAesonOptions (ParamSchema (SwaggerKindNormal * t)) Source # 
HasSwaggerAesonOptions (ParamSchema (SwaggerKindParamOtherSchema *)) Source # 
HasSwaggerAesonOptions (ParamSchema (SwaggerKindSchema *)) Source # 
HasUniqueItems (ParamSchema t0) (Maybe Bool) Source # 
HasType (ParamSchema t0) (SwaggerType t0) Source # 
HasPattern (ParamSchema t0) (Maybe Pattern) Source # 
HasMultipleOf (ParamSchema t0) (Maybe Scientific) Source # 
HasMinimum (ParamSchema t0) (Maybe Scientific) Source # 
HasMinLength (ParamSchema t0) (Maybe Integer) Source # 
HasMinItems (ParamSchema t0) (Maybe Integer) Source # 
HasMaximum (ParamSchema t0) (Maybe Scientific) Source # 
HasMaxLength (ParamSchema t0) (Maybe Integer) Source # 
HasMaxItems (ParamSchema t0) (Maybe Integer) Source # 
HasItems (ParamSchema t0) (Maybe (SwaggerItems t0)) Source # 
HasFormat (ParamSchema t0) (Maybe Format) Source # 
HasExclusiveMinimum (ParamSchema t0) (Maybe Bool) Source # 
HasExclusiveMaximum (ParamSchema t0) (Maybe Bool) Source # 
HasEnum (ParamSchema t0) (Maybe [Value]) Source # 
HasDefault (ParamSchema t0) (Maybe Value) Source # 
type Rep (ParamSchema t) Source # 
type Rep (ParamSchema t) = D1 (MetaData "ParamSchema" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "ParamSchema" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Value))) (S1 (MetaSel (Just Symbol "_paramSchemaType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SwaggerType t)))) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaFormat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Format))) (S1 (MetaSel (Just Symbol "_paramSchemaItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SwaggerItems t)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaMaximum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Scientific))) (S1 (MetaSel (Just Symbol "_paramSchemaExclusiveMaximum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaMinimum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Scientific))) (S1 (MetaSel (Just Symbol "_paramSchemaExclusiveMinimum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaMaxLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "_paramSchemaMinLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Pattern))) (S1 (MetaSel (Just Symbol "_paramSchemaMaxItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaMinItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "_paramSchemaUniqueItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_paramSchemaEnum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Value]))) (S1 (MetaSel (Just Symbol "_paramSchemaMultipleOf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Scientific))))))))
type Code (ParamSchema t0) Source # 
type Code (ParamSchema t0) = (:) [*] ((:) * (Maybe Value) ((:) * (SwaggerType t0) ((:) * (Maybe Format) ((:) * (Maybe (SwaggerItems t0)) ((:) * (Maybe Scientific) ((:) * (Maybe Bool) ((:) * (Maybe Scientific) ((:) * (Maybe Bool) ((:) * (Maybe Integer) ((:) * (Maybe Integer) ((:) * (Maybe Pattern) ((:) * (Maybe Integer) ((:) * (Maybe Integer) ((:) * (Maybe Bool) ((:) * (Maybe [Value]) ((:) * (Maybe Scientific) ([] *))))))))))))))))) ([] [*])

data Schema Source #

Instances

Eq Schema Source # 

Methods

(==) :: Schema -> Schema -> Bool #

(/=) :: Schema -> Schema -> Bool #

Data Schema Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Schema -> c Schema #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Schema #

toConstr :: Schema -> Constr #

dataTypeOf :: Schema -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Schema) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema) #

gmapT :: (forall b. Data b => b -> b) -> Schema -> Schema #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r #

gmapQ :: (forall d. Data d => d -> u) -> Schema -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Schema -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

Show Schema Source # 
Generic Schema Source # 

Associated Types

type Rep Schema :: * -> * #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Monoid Schema Source # 
ToJSON Schema Source # 
FromJSON Schema Source # 
Generic Schema Source # 

Associated Types

type Code Schema :: [[*]] #

Methods

from :: Schema -> Rep Schema #

to :: Rep Schema -> Schema #

HasDatatypeInfo Schema Source # 
SwaggerMonoid Schema Source # 
HasSwaggerAesonOptions Schema Source # 
HasSchema NamedSchema Schema Source # 
HasExternalDocs Schema (Maybe ExternalDocs) Source # 
HasDefinitions Swagger (Definitions Schema) Source # 
HasTitle Schema (Maybe Text) Source # 
HasDescription Schema (Maybe Text) Source # 
HasSchema Response (Maybe (Referenced Schema)) Source # 
HasRequired Schema [ParamName] Source # 
HasParamSchema Schema (ParamSchema (SwaggerKindSchema Type)) Source # 
HasXml Schema (Maybe Xml) Source # 
HasReadOnly Schema (Maybe Bool) Source # 
HasMinProperties Schema (Maybe Integer) Source # 
HasMaxProperties Schema (Maybe Integer) Source # 
HasExample Schema (Maybe Value) Source # 
HasDiscriminator Schema (Maybe Text) Source # 
HasAllOf Schema (Maybe [Schema]) Source # 
HasAdditionalProperties Schema (Maybe (Referenced Schema)) Source # 
HasType Schema (SwaggerType (SwaggerKindSchema *)) Source # 
HasDefault Schema (Maybe Value) Source # 
HasProperties Schema (InsOrdHashMap Text (Referenced Schema)) Source # 
ToJSON (Referenced Schema) Source # 
FromJSON (Referenced Schema) Source # 
type Rep Schema Source # 
type Rep Schema = D1 (MetaData "Schema" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Schema" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_schemaTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_schemaDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_schemaRequired") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParamName])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_schemaAllOf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Schema]))) (S1 (MetaSel (Just Symbol "_schemaProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap Text (Referenced Schema))))) ((:*:) (S1 (MetaSel (Just Symbol "_schemaAdditionalProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Referenced Schema)))) (S1 (MetaSel (Just Symbol "_schemaDiscriminator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_schemaReadOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_schemaXml") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Xml))) (S1 (MetaSel (Just Symbol "_schemaExternalDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalDocs))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_schemaExample") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Value))) (S1 (MetaSel (Just Symbol "_schemaMaxProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "_schemaMinProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "_schemaParamSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParamSchema (SwaggerKindSchema *)))))))))
type Code Schema Source # 
type Code Schema = (:) [*] ((:) * (Maybe Text) ((:) * (Maybe Text) ((:) * [ParamName] ((:) * (Maybe [Schema]) ((:) * (InsOrdHashMap Text (Referenced Schema)) ((:) * (Maybe (Referenced Schema)) ((:) * (Maybe Text) ((:) * (Maybe Bool) ((:) * (Maybe Xml) ((:) * (Maybe ExternalDocs) ((:) * (Maybe Value) ((:) * (Maybe Integer) ((:) * (Maybe Integer) ((:) * (ParamSchema (SwaggerKindSchema Type)) ([] *))))))))))))))) ([] [*])

data NamedSchema Source #

A Schema with an optional name. This name can be used in references.

Instances

Eq NamedSchema Source # 
Data NamedSchema Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamedSchema -> c NamedSchema #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NamedSchema #

toConstr :: NamedSchema -> Constr #

dataTypeOf :: NamedSchema -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NamedSchema) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NamedSchema) #

gmapT :: (forall b. Data b => b -> b) -> NamedSchema -> NamedSchema #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamedSchema -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamedSchema -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamedSchema -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedSchema -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema #

Show NamedSchema Source # 
Generic NamedSchema Source # 

Associated Types

type Rep NamedSchema :: * -> * #

HasSchema NamedSchema Schema Source # 
HasName NamedSchema (Maybe Text) Source # 
HasParamSchema NamedSchema (ParamSchema (SwaggerKindSchema *)) Source # 
HasType NamedSchema (SwaggerType (SwaggerKindSchema *)) Source # 
type Rep NamedSchema Source # 
type Rep NamedSchema = D1 (MetaData "NamedSchema" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "NamedSchema" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_namedSchemaName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_namedSchemaSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Schema))))

data SwaggerItems t where Source #

Items for SwaggerArray schemas.

SwaggerItemsPrimitive should be used only for query params, headers and path pieces. The CollectionFormat t parameter specifies how elements of an array should be displayed. Note that fmt in SwaggerItemsPrimitive fmt schema specifies format for elements of type schema. This is different from the original Swagger's Items Object.

SwaggerItemsObject should be used to specify homogenous array Schemas.

SwaggerItemsArray should be used to specify tuple Schemas.

Instances

HasParamSchema s (ParamSchema t) => HasItems s (Maybe (SwaggerItems t)) Source # 

Methods

items :: Lens' s (Maybe (SwaggerItems t)) Source #

Eq (SwaggerItems t) Source # 
Data t => Data (SwaggerItems (SwaggerKindNormal * t)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerItems (SwaggerKindNormal * t) -> c (SwaggerItems (SwaggerKindNormal * t)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerItems (SwaggerKindNormal * t)) #

toConstr :: SwaggerItems (SwaggerKindNormal * t) -> Constr #

dataTypeOf :: SwaggerItems (SwaggerKindNormal * t) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerItems (SwaggerKindNormal * t))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerItems (SwaggerKindNormal * t))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerItems (SwaggerKindNormal * t) -> SwaggerItems (SwaggerKindNormal * t) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindNormal * t) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindNormal * t) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindNormal * t) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindNormal * t) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindNormal * t) -> m (SwaggerItems (SwaggerKindNormal * t)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindNormal * t) -> m (SwaggerItems (SwaggerKindNormal * t)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindNormal * t) -> m (SwaggerItems (SwaggerKindNormal * t)) #

Data (SwaggerItems (SwaggerKindParamOtherSchema *)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> c (SwaggerItems (SwaggerKindParamOtherSchema *)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerItems (SwaggerKindParamOtherSchema *)) #

toConstr :: SwaggerItems (SwaggerKindParamOtherSchema *) -> Constr #

dataTypeOf :: SwaggerItems (SwaggerKindParamOtherSchema *) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerItems (SwaggerKindParamOtherSchema *))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerItems (SwaggerKindParamOtherSchema *))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> SwaggerItems (SwaggerKindParamOtherSchema *) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindParamOtherSchema *) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindParamOtherSchema *) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> m (SwaggerItems (SwaggerKindParamOtherSchema *)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> m (SwaggerItems (SwaggerKindParamOtherSchema *)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindParamOtherSchema *) -> m (SwaggerItems (SwaggerKindParamOtherSchema *)) #

Data (SwaggerItems (SwaggerKindSchema *)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwaggerItems (SwaggerKindSchema *) -> c (SwaggerItems (SwaggerKindSchema *)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SwaggerItems (SwaggerKindSchema *)) #

toConstr :: SwaggerItems (SwaggerKindSchema *) -> Constr #

dataTypeOf :: SwaggerItems (SwaggerKindSchema *) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SwaggerItems (SwaggerKindSchema *))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SwaggerItems (SwaggerKindSchema *))) #

gmapT :: (forall b. Data b => b -> b) -> SwaggerItems (SwaggerKindSchema *) -> SwaggerItems (SwaggerKindSchema *) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindSchema *) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwaggerItems (SwaggerKindSchema *) -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindSchema *) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwaggerItems (SwaggerKindSchema *) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindSchema *) -> m (SwaggerItems (SwaggerKindSchema *)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindSchema *) -> m (SwaggerItems (SwaggerKindSchema *)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwaggerItems (SwaggerKindSchema *) -> m (SwaggerItems (SwaggerKindSchema *)) #

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 Xml Source #

Constructors

Xml 

Fields

  • _xmlName :: Maybe Text

    Replaces the name of the element/attribute used for the described schema property. When defined within the SwaggerItems (items), it will affect the name of the individual XML elements within the list. When defined alongside type being array (outside the items), it will affect the wrapping element and only if wrapped is true. If wrapped is false, it will be ignored.

  • _xmlNamespace :: Maybe Text

    The URL of the namespace definition. Value SHOULD be in the form of a URL.

  • _xmlPrefix :: Maybe Text

    The prefix to be used for the name.

  • _xmlAttribute :: Maybe Bool

    Declares whether the property definition translates to an attribute instead of an element. Default value is False.

  • _xmlWrapped :: Maybe Bool

    MAY be used only for an array definition. Signifies whether the array is wrapped (for example, <books><book><book></books>) or unwrapped (<book><book>). Default value is False. The definition takes effect only when defined alongside type being array (outside the items).

Instances

Eq Xml Source # 

Methods

(==) :: Xml -> Xml -> Bool #

(/=) :: Xml -> Xml -> Bool #

Data Xml Source # 

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 #

toConstr :: Xml -> Constr #

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 # 

Methods

showsPrec :: Int -> Xml -> ShowS #

show :: Xml -> String #

showList :: [Xml] -> ShowS #

Generic Xml Source # 

Associated Types

type Rep Xml :: * -> * #

Methods

from :: Xml -> Rep Xml x #

to :: Rep Xml x -> Xml #

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 # 

type Pattern = Text Source #

Regex pattern for string type.

Responses

data Responses 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

Eq Responses Source # 
Data Responses Source # 

Methods

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 # 

Associated Types

type Rep Responses :: * -> * #

Monoid Responses Source # 
ToJSON Responses Source # 
FromJSON Responses Source # 
Generic Responses Source # 

Associated Types

type Code Responses :: [[*]] #

HasDatatypeInfo Responses Source # 
SwaggerMonoid Responses Source # 
AesonDefaultValue Responses Source # 
HasSwaggerAesonOptions Responses Source # 
HasResponses Operation Responses Source # 
HasDefault Responses (Maybe (Referenced Response)) Source # 
HasResponses Responses (InsOrdHashMap HttpStatusCode (Referenced Response)) Source # 
type Rep Responses Source # 
type Rep Responses = D1 (MetaData "Responses" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Responses" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_responsesDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Referenced Response)))) (S1 (MetaSel (Just Symbol "_responsesResponses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap HttpStatusCode (Referenced Response))))))
type Code Responses Source # 
type Code Responses = (:) [*] ((:) * (Maybe (Referenced Response)) ((:) * (InsOrdHashMap HttpStatusCode (Referenced Response)) ([] *))) ([] [*])
type Index Responses # 
type IxValue Responses # 

data Response Source #

Describes a single response from an API Operation.

Constructors

Response 

Fields

Instances

Eq Response Source # 
Data Response Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Response -> c Response #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Response #

toConstr :: Response -> Constr #

dataTypeOf :: Response -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Response) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response) #

gmapT :: (forall b. Data b => b -> b) -> Response -> Response #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Response -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Response -> r #

gmapQ :: (forall d. Data d => d -> u) -> Response -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Response -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Response -> m Response #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Response -> m Response #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Response -> m Response #

Show Response Source # 
IsString Response Source # 
Generic Response Source # 

Associated Types

type Rep Response :: * -> * #

Methods

from :: Response -> Rep Response x #

to :: Rep Response x -> Response #

Monoid Response Source # 
ToJSON Response Source # 
FromJSON Response Source # 
Generic Response Source # 

Associated Types

type Code Response :: [[*]] #

HasDatatypeInfo Response Source # 
SwaggerMonoid Response Source # 
HasSwaggerAesonOptions Response Source # 
HasDescription Response Text Source # 
HasResponses Swagger (Definitions Response) Source # 
HasSchema Response (Maybe (Referenced Schema)) Source # 
HasDefault Responses (Maybe (Referenced Response)) Source # 
HasExamples Response (Maybe Example) Source # 
HasResponses Responses (InsOrdHashMap HttpStatusCode (Referenced Response)) Source # 
HasHeaders Response (InsOrdHashMap HeaderName Header) Source # 
ToJSON (Referenced Response) Source # 
FromJSON (Referenced Response) Source # 
type Rep Response Source # 
type Rep Response = D1 (MetaData "Response" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "Response" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_responseDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_responseSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Referenced Schema))))) ((:*:) (S1 (MetaSel (Just Symbol "_responseHeaders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap HeaderName Header))) (S1 (MetaSel (Just Symbol "_responseExamples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Example))))))
type Code Response Source # 
type Code Response = (:) [*] ((:) * Text ((:) * (Maybe (Referenced Schema)) ((:) * (InsOrdHashMap HeaderName Header) ((:) * (Maybe Example) ([] *))))) ([] [*])

Security

data SecurityScheme Source #

Constructors

SecurityScheme 

Fields

Instances

Eq SecurityScheme Source # 
Data SecurityScheme Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecurityScheme #

toConstr :: SecurityScheme -> Constr #

dataTypeOf :: SecurityScheme -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecurityScheme) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecurityScheme) #

gmapT :: (forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecurityScheme -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecurityScheme -> m SecurityScheme #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityScheme -> m SecurityScheme #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityScheme -> m SecurityScheme #

Show SecurityScheme Source # 
Generic SecurityScheme Source # 

Associated Types

type Rep SecurityScheme :: * -> * #

ToJSON SecurityScheme Source # 
FromJSON SecurityScheme Source # 
Generic SecurityScheme Source # 
HasDatatypeInfo SecurityScheme Source # 
HasSwaggerAesonOptions SecurityScheme Source # 
HasType SecurityScheme SecuritySchemeType Source # 
HasSecurityDefinitions Swagger (Definitions SecurityScheme) Source # 
HasDescription SecurityScheme (Maybe Text) Source # 
type Rep SecurityScheme Source # 
type Rep SecurityScheme = D1 (MetaData "SecurityScheme" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "SecurityScheme" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_securitySchemeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SecuritySchemeType)) (S1 (MetaSel (Just Symbol "_securitySchemeDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))
type Code SecurityScheme Source # 
type Code SecurityScheme = (:) [*] ((:) * SecuritySchemeType ((:) * (Maybe Text) ([] *))) ([] [*])

data SecuritySchemeType Source #

Instances

Eq SecuritySchemeType Source # 
Data SecuritySchemeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecuritySchemeType -> c SecuritySchemeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecuritySchemeType #

toConstr :: SecuritySchemeType -> Constr #

dataTypeOf :: SecuritySchemeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecuritySchemeType) #

gmapT :: (forall b. Data b => b -> b) -> SecuritySchemeType -> SecuritySchemeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecuritySchemeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecuritySchemeType -> m SecuritySchemeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecuritySchemeType -> m SecuritySchemeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecuritySchemeType -> m SecuritySchemeType #

Show SecuritySchemeType Source # 
Generic SecuritySchemeType Source # 
ToJSON SecuritySchemeType Source # 
FromJSON SecuritySchemeType Source # 
AesonDefaultValue SecuritySchemeType Source # 
HasType SecurityScheme SecuritySchemeType Source # 
type Rep SecuritySchemeType Source # 
type Rep SecuritySchemeType = D1 (MetaData "SecuritySchemeType" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) ((:+:) (C1 (MetaCons "SecuritySchemeBasic" PrefixI False) U1) ((:+:) (C1 (MetaCons "SecuritySchemeApiKey" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ApiKeyParams))) (C1 (MetaCons "SecuritySchemeOAuth2" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OAuth2Params)))))

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).

Instances

Eq SecurityRequirement Source # 
Data SecurityRequirement Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecurityRequirement -> c SecurityRequirement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecurityRequirement #

toConstr :: SecurityRequirement -> Constr #

dataTypeOf :: SecurityRequirement -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecurityRequirement) #

gmapT :: (forall b. Data b => b -> b) -> SecurityRequirement -> SecurityRequirement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecurityRequirement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecurityRequirement -> m SecurityRequirement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityRequirement -> m SecurityRequirement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityRequirement -> m SecurityRequirement #

Read SecurityRequirement Source # 
Show SecurityRequirement Source # 
Monoid SecurityRequirement Source # 
ToJSON SecurityRequirement Source # 
FromJSON SecurityRequirement Source # 
HasSecurity Operation [SecurityRequirement] Source # 
HasSecurity Swagger [SecurityRequirement] Source # 

API key

data ApiKeyParams Source #

Constructors

ApiKeyParams 

Fields

Instances

Eq ApiKeyParams Source # 
Data ApiKeyParams Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApiKeyParams #

toConstr :: ApiKeyParams -> Constr #

dataTypeOf :: ApiKeyParams -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApiKeyParams) #

gmapT :: (forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApiKeyParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams #

Show ApiKeyParams Source # 
Generic ApiKeyParams Source # 

Associated Types

type Rep ApiKeyParams :: * -> * #

ToJSON ApiKeyParams Source # 
FromJSON ApiKeyParams Source # 
type Rep ApiKeyParams Source # 
type Rep ApiKeyParams = D1 (MetaData "ApiKeyParams" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "ApiKeyParams" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_apiKeyName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_apiKeyIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ApiKeyLocation))))

data ApiKeyLocation Source #

The location of the API key.

Constructors

ApiKeyQuery 
ApiKeyHeader 

Instances

Eq ApiKeyLocation Source # 
Data ApiKeyLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApiKeyLocation #

toConstr :: ApiKeyLocation -> Constr #

dataTypeOf :: ApiKeyLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApiKeyLocation) #

gmapT :: (forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApiKeyLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApiKeyLocation -> m ApiKeyLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiKeyLocation -> m ApiKeyLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiKeyLocation -> m ApiKeyLocation #

Show ApiKeyLocation Source # 
Generic ApiKeyLocation Source # 

Associated Types

type Rep ApiKeyLocation :: * -> * #

ToJSON ApiKeyLocation Source # 
FromJSON ApiKeyLocation Source # 
type Rep ApiKeyLocation Source # 
type Rep ApiKeyLocation = D1 (MetaData "ApiKeyLocation" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) ((:+:) (C1 (MetaCons "ApiKeyQuery" PrefixI False) U1) (C1 (MetaCons "ApiKeyHeader" PrefixI False) U1))

OAuth2

data OAuth2Params Source #

Constructors

OAuth2Params 

Fields

Instances

Eq OAuth2Params Source # 
Data OAuth2Params Source # 

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 # 
Generic OAuth2Params Source # 

Associated Types

type Rep OAuth2Params :: * -> * #

ToJSON OAuth2Params Source # 
FromJSON OAuth2Params Source # 
Generic OAuth2Params Source # 

Associated Types

type Code OAuth2Params :: [[*]] #

HasDatatypeInfo OAuth2Params Source # 
HasSwaggerAesonOptions OAuth2Params Source # 
type Rep OAuth2Params Source # 
type Rep OAuth2Params = D1 (MetaData "OAuth2Params" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "OAuth2Params" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oauth2Flow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OAuth2Flow)) (S1 (MetaSel (Just Symbol "_oauth2Scopes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InsOrdHashMap Text Text)))))
type Code OAuth2Params Source # 
type Code OAuth2Params = (:) [*] ((:) * OAuth2Flow ((:) * (InsOrdHashMap Text Text) ([] *))) ([] [*])

data OAuth2Flow Source #

Instances

Eq OAuth2Flow Source # 
Data OAuth2Flow Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OAuth2Flow #

toConstr :: OAuth2Flow -> Constr #

dataTypeOf :: OAuth2Flow -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OAuth2Flow) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth2Flow) #

gmapT :: (forall b. Data b => b -> b) -> OAuth2Flow -> OAuth2Flow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r #

gmapQ :: (forall d. Data d => d -> u) -> OAuth2Flow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth2Flow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow #

Show OAuth2Flow Source # 
Generic OAuth2Flow Source # 

Associated Types

type Rep OAuth2Flow :: * -> * #

ToJSON OAuth2Flow Source # 
FromJSON OAuth2Flow Source # 
AesonDefaultValue OAuth2Flow Source # 
type Rep OAuth2Flow Source # 

type AuthorizationURL = Text Source #

The authorization URL to be used for OAuth2 flow. This SHOULD be in the form of a URL.

type TokenURL = Text Source #

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

Eq ExternalDocs Source # 
Data ExternalDocs Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExternalDocs #

toConstr :: ExternalDocs -> Constr #

dataTypeOf :: ExternalDocs -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExternalDocs) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExternalDocs) #

gmapT :: (forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExternalDocs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs #

Ord ExternalDocs Source # 
Show ExternalDocs Source # 
Generic ExternalDocs Source # 

Associated Types

type Rep ExternalDocs :: * -> * #

Monoid ExternalDocs Source # 
ToJSON ExternalDocs Source # 
FromJSON ExternalDocs Source # 
SwaggerMonoid ExternalDocs Source # 
HasUrl ExternalDocs URL Source # 
HasExternalDocs Tag (Maybe ExternalDocs) Source # 
HasExternalDocs Schema (Maybe ExternalDocs) Source # 
HasExternalDocs Operation (Maybe ExternalDocs) Source # 
HasExternalDocs Swagger (Maybe ExternalDocs) Source # 
HasDescription ExternalDocs (Maybe Text) Source # 
type Rep ExternalDocs Source # 
type Rep ExternalDocs = D1 (MetaData "ExternalDocs" "Data.Swagger.Internal" "swagger2-2.1.4.1-IB5cgNouzkAL9WkXeV9lhb" False) (C1 (MetaCons "ExternalDocs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_externalDocsDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_externalDocsUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL))))

References

newtype Reference Source #

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 # 

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 # 
FromJSON Reference Source # 

data Referenced a Source #

Constructors

Ref Reference 
Inline a 

Instances

Functor Referenced Source # 

Methods

fmap :: (a -> b) -> Referenced a -> Referenced b #

(<$) :: a -> Referenced b -> Referenced a #

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 # 

Methods

(==) :: Referenced a -> Referenced a -> Bool #

(/=) :: Referenced a -> Referenced a -> Bool #

Data a => Data (Referenced a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Referenced a -> c (Referenced a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Referenced a) #

toConstr :: Referenced a -> Constr #

dataTypeOf :: Referenced a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Referenced a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Referenced a)) #

gmapT :: (forall b. Data b => b -> b) -> Referenced a -> Referenced a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Referenced a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Referenced a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Referenced a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Referenced a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a) #

Show a => Show (Referenced a) Source # 
IsString a => IsString (Referenced a) Source # 

Methods

fromString :: String -> Referenced a #

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 # 

Miscellaneous

newtype MimeList Source #

Constructors

MimeList 

Fields

Instances

Eq MimeList Source # 
Data MimeList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MimeList -> c MimeList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MimeList #

toConstr :: MimeList -> Constr #

dataTypeOf :: MimeList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MimeList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MimeList) #

gmapT :: (forall b. Data b => b -> b) -> MimeList -> MimeList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MimeList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MimeList -> r #

gmapQ :: (forall d. Data d => d -> u) -> MimeList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MimeList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MimeList -> m MimeList #

Show MimeList Source # 
Monoid MimeList Source # 
ToJSON MimeList Source # 
FromJSON MimeList Source # 
SwaggerMonoid MimeList Source # 
AesonDefaultValue MimeList Source # 
HasProduces Swagger MimeList Source # 
HasConsumes Swagger MimeList Source # 
HasProduces Operation (Maybe MimeList) Source # 
HasConsumes Operation (Maybe MimeList) Source # 

newtype URL Source #

Constructors

URL 

Fields

Instances

Eq URL Source # 

Methods

(==) :: URL -> URL -> Bool #

(/=) :: URL -> URL -> Bool #

Data URL Source # 

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 #

toConstr :: URL -> Constr #

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 # 

Methods

compare :: URL -> URL -> Ordering #

(<) :: URL -> URL -> Bool #

(<=) :: URL -> URL -> Bool #

(>) :: URL -> URL -> Bool #

(>=) :: URL -> URL -> Bool #

max :: URL -> URL -> URL #

min :: URL -> URL -> URL #

Show URL Source # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

ToJSON URL Source # 
FromJSON URL Source # 
SwaggerMonoid URL Source # 
HasUrl ExternalDocs URL Source # 
HasUrl License (Maybe URL) Source # 
HasUrl Contact (Maybe URL) Source #