{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Swagger.Internal where

import Prelude ()
import Prelude.Compat

import           Control.Lens             ((&), (.~), (?~))
import           Control.Applicative
import           Data.Aeson
import qualified Data.Aeson.Types         as JSON
import           Data.Data                (Data(..), Typeable, mkConstr, mkDataType, Fixity(..), Constr, DataType, constrIndex)
import           Data.Hashable            (Hashable)
import qualified Data.HashMap.Strict      as HashMap
import           Data.HashSet.InsOrd      (InsOrdHashSet)
import           Data.Map                 (Map)
import qualified Data.Map                 as Map
import           Data.Monoid              (Monoid (..))
import           Data.Semigroup.Compat    (Semigroup (..))
import           Data.Scientific          (Scientific)
import           Data.String              (IsString(..))
import           Data.Text                (Text)
import qualified Data.Text                as Text
import           GHC.Generics             (Generic)
import           Network.Socket           (HostName, PortNumber)
import           Network.HTTP.Media       (MediaType)
import           Text.Read                (readMaybe)

import           Data.HashMap.Strict.InsOrd (InsOrdHashMap)
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
import qualified Data.Aeson.KeyMap          as KM

import Generics.SOP.TH                  (deriveGeneric)
import Data.Swagger.Internal.AesonUtils (sopSwaggerGenericToJSON
                                        ,sopSwaggerGenericToJSONWithOpts
                                        ,sopSwaggerGenericParseJSON
                                        ,HasSwaggerAesonOptions(..)
                                        ,AesonDefaultValue(..)
                                        ,mkSwaggerAesonOptions
                                        ,saoAdditionalPairs
                                        ,saoSubObject)
import Data.Swagger.Internal.Utils
import Data.Swagger.Internal.AesonUtils (sopSwaggerGenericToEncoding)

-- $setup
-- >>> :seti -XDataKinds
-- >>> import Data.Aeson

-- | A list of definitions that can be used in references.
type Definitions = InsOrdHashMap Text

-- | This is the root document object for the API specification.
data Swagger = Swagger
  { -- | Provides metadata about the API.
    -- The metadata can be used by the clients if needed.
    Swagger -> Info
_swaggerInfo :: Info

    -- | 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).
  , Swagger -> Maybe Host
_swaggerHost :: Maybe Host

    -- | 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 (/).
  , Swagger -> Maybe FilePath
_swaggerBasePath :: Maybe FilePath

    -- | 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.
  , Swagger -> Maybe [Scheme]
_swaggerSchemes :: Maybe [Scheme]

    -- | A list of MIME types the APIs can consume.
    -- This is global to all APIs but can be overridden on specific API calls.
  , Swagger -> MimeList
_swaggerConsumes :: MimeList

    -- | A list of MIME types the APIs can produce.
    -- This is global to all APIs but can be overridden on specific API calls.
  , Swagger -> MimeList
_swaggerProduces :: MimeList

    -- | 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.
  , Swagger -> InsOrdHashMap FilePath PathItem
_swaggerPaths :: InsOrdHashMap FilePath PathItem

    -- | An object to hold data types produced and consumed by operations.
  , Swagger -> Definitions Schema
_swaggerDefinitions :: Definitions Schema

    -- | An object to hold parameters that can be used across operations.
    -- This property does not define global parameters for all operations.
  , Swagger -> Definitions Param
_swaggerParameters :: Definitions Param

    -- | An object to hold responses that can be used across operations.
    -- This property does not define global responses for all operations.
  , Swagger -> Definitions Response
_swaggerResponses :: Definitions Response

    -- | Security scheme definitions that can be used across the specification.
  , Swagger -> SecurityDefinitions
_swaggerSecurityDefinitions :: SecurityDefinitions

    -- | 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.
  , Swagger -> [SecurityRequirement]
_swaggerSecurity :: [SecurityRequirement]

    -- | 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.
  , Swagger -> InsOrdHashSet Tag
_swaggerTags :: InsOrdHashSet Tag

    -- | Additional external documentation.
  , Swagger -> Maybe ExternalDocs
_swaggerExternalDocs :: Maybe ExternalDocs
  } deriving (Swagger -> Swagger -> Bool
(Swagger -> Swagger -> Bool)
-> (Swagger -> Swagger -> Bool) -> Eq Swagger
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Swagger -> Swagger -> Bool
$c/= :: Swagger -> Swagger -> Bool
== :: Swagger -> Swagger -> Bool
$c== :: Swagger -> Swagger -> Bool
Eq, Int -> Swagger -> ShowS
[Swagger] -> ShowS
Swagger -> FilePath
(Int -> Swagger -> ShowS)
-> (Swagger -> FilePath) -> ([Swagger] -> ShowS) -> Show Swagger
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Swagger] -> ShowS
$cshowList :: [Swagger] -> ShowS
show :: Swagger -> FilePath
$cshow :: Swagger -> FilePath
showsPrec :: Int -> Swagger -> ShowS
$cshowsPrec :: Int -> Swagger -> ShowS
Show, (forall x. Swagger -> Rep Swagger x)
-> (forall x. Rep Swagger x -> Swagger) -> Generic Swagger
forall x. Rep Swagger x -> Swagger
forall x. Swagger -> Rep Swagger x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Swagger x -> Swagger
$cfrom :: forall x. Swagger -> Rep Swagger x
Generic, Typeable Swagger
DataType
Constr
Typeable Swagger =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Swagger -> c Swagger)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Swagger)
-> (Swagger -> Constr)
-> (Swagger -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Swagger))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Swagger))
-> ((forall b. Data b => b -> b) -> Swagger -> Swagger)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Swagger -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Swagger -> r)
-> (forall u. (forall d. Data d => d -> u) -> Swagger -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Swagger -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Swagger -> m Swagger)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Swagger -> m Swagger)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Swagger -> m Swagger)
-> Data Swagger
Swagger -> DataType
Swagger -> Constr
(forall b. Data b => b -> b) -> Swagger -> Swagger
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Swagger -> c Swagger
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Swagger
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Swagger -> u
forall u. (forall d. Data d => d -> u) -> Swagger -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Swagger -> m Swagger
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Swagger -> m Swagger
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Swagger
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Swagger -> c Swagger
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Swagger)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Swagger)
$cSwagger :: Constr
$tSwagger :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Swagger -> m Swagger
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Swagger -> m Swagger
gmapMp :: (forall d. Data d => d -> m d) -> Swagger -> m Swagger
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Swagger -> m Swagger
gmapM :: (forall d. Data d => d -> m d) -> Swagger -> m Swagger
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Swagger -> m Swagger
gmapQi :: Int -> (forall d. Data d => d -> u) -> Swagger -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Swagger -> u
gmapQ :: (forall d. Data d => d -> u) -> Swagger -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Swagger -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Swagger -> r
gmapT :: (forall b. Data b => b -> b) -> Swagger -> Swagger
$cgmapT :: (forall b. Data b => b -> b) -> Swagger -> Swagger
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Swagger)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Swagger)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Swagger)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Swagger)
dataTypeOf :: Swagger -> DataType
$cdataTypeOf :: Swagger -> DataType
toConstr :: Swagger -> Constr
$ctoConstr :: Swagger -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Swagger
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Swagger
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Swagger -> c Swagger
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Swagger -> c Swagger
$cp1Data :: Typeable Swagger
Data, Typeable)

-- | 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.
data Info = Info
  { -- | The title of the application.
    Info -> Text
_infoTitle :: Text

    -- | A short description of the application.
    -- GFM syntax can be used for rich text representation.
  , Info -> Maybe Text
_infoDescription :: Maybe Text

    -- | The Terms of Service for the API.
  , Info -> Maybe Text
_infoTermsOfService :: Maybe Text

    -- | The contact information for the exposed API.
  , Info -> Maybe Contact
_infoContact :: Maybe Contact

    -- | The license information for the exposed API.
  , Info -> Maybe License
_infoLicense :: Maybe License

    -- | Provides the version of the application API
    -- (not to be confused with the specification version).
  , Info -> Text
_infoVersion :: Text
  } deriving (Info -> Info -> Bool
(Info -> Info -> Bool) -> (Info -> Info -> Bool) -> Eq Info
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Info -> Info -> Bool
$c/= :: Info -> Info -> Bool
== :: Info -> Info -> Bool
$c== :: Info -> Info -> Bool
Eq, Int -> Info -> ShowS
[Info] -> ShowS
Info -> FilePath
(Int -> Info -> ShowS)
-> (Info -> FilePath) -> ([Info] -> ShowS) -> Show Info
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Info] -> ShowS
$cshowList :: [Info] -> ShowS
show :: Info -> FilePath
$cshow :: Info -> FilePath
showsPrec :: Int -> Info -> ShowS
$cshowsPrec :: Int -> Info -> ShowS
Show, (forall x. Info -> Rep Info x)
-> (forall x. Rep Info x -> Info) -> Generic Info
forall x. Rep Info x -> Info
forall x. Info -> Rep Info x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Info x -> Info
$cfrom :: forall x. Info -> Rep Info x
Generic, Typeable Info
DataType
Constr
Typeable Info =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Info -> c Info)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Info)
-> (Info -> Constr)
-> (Info -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Info))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info))
-> ((forall b. Data b => b -> b) -> Info -> Info)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r)
-> (forall u. (forall d. Data d => d -> u) -> Info -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Info -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Info -> m Info)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Info -> m Info)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Info -> m Info)
-> Data Info
Info -> DataType
Info -> Constr
(forall b. Data b => b -> b) -> Info -> Info
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
forall u. (forall d. Data d => d -> u) -> Info -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Info -> m Info
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Info)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info)
$cInfo :: Constr
$tInfo :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Info -> m Info
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info
gmapMp :: (forall d. Data d => d -> m d) -> Info -> m Info
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info
gmapM :: (forall d. Data d => d -> m d) -> Info -> m Info
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Info -> m Info
gmapQi :: Int -> (forall d. Data d => d -> u) -> Info -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
gmapQ :: (forall d. Data d => d -> u) -> Info -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Info -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
gmapT :: (forall b. Data b => b -> b) -> Info -> Info
$cgmapT :: (forall b. Data b => b -> b) -> Info -> Info
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Info)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Info)
dataTypeOf :: Info -> DataType
$cdataTypeOf :: Info -> DataType
toConstr :: Info -> Constr
$ctoConstr :: Info -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
$cp1Data :: Typeable Info
Data, Typeable)

-- | Contact information for the exposed API.
data Contact = Contact
  { -- | The identifying name of the contact person/organization.
    Contact -> Maybe Text
_contactName  :: Maybe Text

    -- | The URL pointing to the contact information.
  , Contact -> Maybe URL
_contactUrl   :: Maybe URL

    -- | The email address of the contact person/organization.
  , Contact -> Maybe Text
_contactEmail :: Maybe Text
  } deriving (Contact -> Contact -> Bool
(Contact -> Contact -> Bool)
-> (Contact -> Contact -> Bool) -> Eq Contact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Contact -> Contact -> Bool
$c/= :: Contact -> Contact -> Bool
== :: Contact -> Contact -> Bool
$c== :: Contact -> Contact -> Bool
Eq, Int -> Contact -> ShowS
[Contact] -> ShowS
Contact -> FilePath
(Int -> Contact -> ShowS)
-> (Contact -> FilePath) -> ([Contact] -> ShowS) -> Show Contact
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Contact] -> ShowS
$cshowList :: [Contact] -> ShowS
show :: Contact -> FilePath
$cshow :: Contact -> FilePath
showsPrec :: Int -> Contact -> ShowS
$cshowsPrec :: Int -> Contact -> ShowS
Show, (forall x. Contact -> Rep Contact x)
-> (forall x. Rep Contact x -> Contact) -> Generic Contact
forall x. Rep Contact x -> Contact
forall x. Contact -> Rep Contact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Contact x -> Contact
$cfrom :: forall x. Contact -> Rep Contact x
Generic, Typeable Contact
DataType
Constr
Typeable Contact =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Contact -> c Contact)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Contact)
-> (Contact -> Constr)
-> (Contact -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Contact))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact))
-> ((forall b. Data b => b -> b) -> Contact -> Contact)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Contact -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Contact -> r)
-> (forall u. (forall d. Data d => d -> u) -> Contact -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Contact -> m Contact)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Contact -> m Contact)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Contact -> m Contact)
-> Data Contact
Contact -> DataType
Contact -> Constr
(forall b. Data b => b -> b) -> Contact -> Contact
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
forall u. (forall d. Data d => d -> u) -> Contact -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contact)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact)
$cContact :: Constr
$tContact :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Contact -> m Contact
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
gmapMp :: (forall d. Data d => d -> m d) -> Contact -> m Contact
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
gmapM :: (forall d. Data d => d -> m d) -> Contact -> m Contact
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
gmapQi :: Int -> (forall d. Data d => d -> u) -> Contact -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
gmapQ :: (forall d. Data d => d -> u) -> Contact -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Contact -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
gmapT :: (forall b. Data b => b -> b) -> Contact -> Contact
$cgmapT :: (forall b. Data b => b -> b) -> Contact -> Contact
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Contact)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contact)
dataTypeOf :: Contact -> DataType
$cdataTypeOf :: Contact -> DataType
toConstr :: Contact -> Constr
$ctoConstr :: Contact -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
$cp1Data :: Typeable Contact
Data, Typeable)

-- | License information for the exposed API.
data License = License
  { -- | The license name used for the API.
    License -> Text
_licenseName :: Text

    -- | A URL to the license used for the API.
  , License -> Maybe URL
_licenseUrl :: Maybe URL
  } deriving (License -> License -> Bool
(License -> License -> Bool)
-> (License -> License -> Bool) -> Eq License
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: License -> License -> Bool
$c/= :: License -> License -> Bool
== :: License -> License -> Bool
$c== :: License -> License -> Bool
Eq, Int -> License -> ShowS
[License] -> ShowS
License -> FilePath
(Int -> License -> ShowS)
-> (License -> FilePath) -> ([License] -> ShowS) -> Show License
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [License] -> ShowS
$cshowList :: [License] -> ShowS
show :: License -> FilePath
$cshow :: License -> FilePath
showsPrec :: Int -> License -> ShowS
$cshowsPrec :: Int -> License -> ShowS
Show, (forall x. License -> Rep License x)
-> (forall x. Rep License x -> License) -> Generic License
forall x. Rep License x -> License
forall x. License -> Rep License x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep License x -> License
$cfrom :: forall x. License -> Rep License x
Generic, Typeable License
DataType
Constr
Typeable License =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> License -> c License)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c License)
-> (License -> Constr)
-> (License -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c License))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License))
-> ((forall b. Data b => b -> b) -> License -> License)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall u. (forall d. Data d => d -> u) -> License -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> License -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> Data License
License -> DataType
License -> Constr
(forall b. Data b => b -> b) -> License -> License
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> License -> u
forall u. (forall d. Data d => d -> u) -> License -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cLicense :: Constr
$tLicense :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapMp :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapM :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
gmapQ :: (forall d. Data d => d -> u) -> License -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapT :: (forall b. Data b => b -> b) -> License -> License
$cgmapT :: (forall b. Data b => b -> b) -> License -> License
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c License)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
dataTypeOf :: License -> DataType
$cdataTypeOf :: License -> DataType
toConstr :: License -> Constr
$ctoConstr :: License -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
$cp1Data :: Typeable License
Data, Typeable)

instance IsString License where
  fromString :: FilePath -> License
fromString s :: FilePath
s = Text -> Maybe URL -> License
License (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe URL
forall a. Maybe a
Nothing

-- | The host (name or ip) serving the API. It MAY include a port.
data Host = Host
  { Host -> FilePath
_hostName :: HostName         -- ^ Host name.
  , Host -> Maybe PortNumber
_hostPort :: Maybe PortNumber -- ^ Optional port.
  } deriving (Host -> Host -> Bool
(Host -> Host -> Bool) -> (Host -> Host -> Bool) -> Eq Host
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Host -> Host -> Bool
$c/= :: Host -> Host -> Bool
== :: Host -> Host -> Bool
$c== :: Host -> Host -> Bool
Eq, Int -> Host -> ShowS
[Host] -> ShowS
Host -> FilePath
(Int -> Host -> ShowS)
-> (Host -> FilePath) -> ([Host] -> ShowS) -> Show Host
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Host] -> ShowS
$cshowList :: [Host] -> ShowS
show :: Host -> FilePath
$cshow :: Host -> FilePath
showsPrec :: Int -> Host -> ShowS
$cshowsPrec :: Int -> Host -> ShowS
Show, (forall x. Host -> Rep Host x)
-> (forall x. Rep Host x -> Host) -> Generic Host
forall x. Rep Host x -> Host
forall x. Host -> Rep Host x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Host x -> Host
$cfrom :: forall x. Host -> Rep Host x
Generic, Typeable)

instance IsString Host where
  fromString :: FilePath -> Host
fromString s :: FilePath
s = FilePath -> Maybe PortNumber -> Host
Host FilePath
s Maybe PortNumber
forall a. Maybe a
Nothing

hostConstr :: Constr
hostConstr :: Constr
hostConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
hostDataType "Host" [] Fixity
Prefix

hostDataType :: DataType
hostDataType :: DataType
hostDataType = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.Host" [Constr
hostConstr]

instance Data Host where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Host
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    1 -> c (Maybe Integer -> Host) -> c Host
forall b r. Data b => c (b -> r) -> c r
k (c (FilePath -> Maybe Integer -> Host) -> c (Maybe Integer -> Host)
forall b r. Data b => c (b -> r) -> c r
k ((FilePath -> Maybe Integer -> Host)
-> c (FilePath -> Maybe Integer -> Host)
forall r. r -> c r
z (\name :: FilePath
name mport :: Maybe Integer
mport -> FilePath -> Maybe PortNumber -> Host
Host FilePath
name (Integer -> PortNumber
forall a. Num a => Integer -> a
fromInteger (Integer -> PortNumber) -> Maybe Integer -> Maybe PortNumber
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
mport))))
    _ -> FilePath -> c Host
forall a. HasCallStack => FilePath -> a
error (FilePath -> c Host) -> FilePath -> c Host
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type Host."
  toConstr :: Host -> Constr
toConstr (Host _ _) = Constr
hostConstr
  dataTypeOf :: Host -> DataType
dataTypeOf _ = DataType
hostDataType

-- | The transfer protocol of the API.
data Scheme
  = Http
  | Https
  | Ws
  | Wss
  deriving (Scheme -> Scheme -> Bool
(Scheme -> Scheme -> Bool)
-> (Scheme -> Scheme -> Bool) -> Eq Scheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scheme -> Scheme -> Bool
$c/= :: Scheme -> Scheme -> Bool
== :: Scheme -> Scheme -> Bool
$c== :: Scheme -> Scheme -> Bool
Eq, Int -> Scheme -> ShowS
[Scheme] -> ShowS
Scheme -> FilePath
(Int -> Scheme -> ShowS)
-> (Scheme -> FilePath) -> ([Scheme] -> ShowS) -> Show Scheme
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Scheme] -> ShowS
$cshowList :: [Scheme] -> ShowS
show :: Scheme -> FilePath
$cshow :: Scheme -> FilePath
showsPrec :: Int -> Scheme -> ShowS
$cshowsPrec :: Int -> Scheme -> ShowS
Show, (forall x. Scheme -> Rep Scheme x)
-> (forall x. Rep Scheme x -> Scheme) -> Generic Scheme
forall x. Rep Scheme x -> Scheme
forall x. Scheme -> Rep Scheme x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Scheme x -> Scheme
$cfrom :: forall x. Scheme -> Rep Scheme x
Generic, Typeable Scheme
DataType
Constr
Typeable Scheme =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Scheme -> c Scheme)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Scheme)
-> (Scheme -> Constr)
-> (Scheme -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Scheme))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme))
-> ((forall b. Data b => b -> b) -> Scheme -> Scheme)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Scheme -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Scheme -> r)
-> (forall u. (forall d. Data d => d -> u) -> Scheme -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Scheme -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Scheme -> m Scheme)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Scheme -> m Scheme)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Scheme -> m Scheme)
-> Data Scheme
Scheme -> DataType
Scheme -> Constr
(forall b. Data b => b -> b) -> Scheme -> Scheme
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scheme -> c Scheme
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scheme
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Scheme -> u
forall u. (forall d. Data d => d -> u) -> Scheme -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scheme -> m Scheme
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scheme -> m Scheme
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scheme
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scheme -> c Scheme
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scheme)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme)
$cWss :: Constr
$cWs :: Constr
$cHttps :: Constr
$cHttp :: Constr
$tScheme :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Scheme -> m Scheme
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scheme -> m Scheme
gmapMp :: (forall d. Data d => d -> m d) -> Scheme -> m Scheme
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scheme -> m Scheme
gmapM :: (forall d. Data d => d -> m d) -> Scheme -> m Scheme
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scheme -> m Scheme
gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Scheme -> u
gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Scheme -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r
gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme
$cgmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Scheme)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scheme)
dataTypeOf :: Scheme -> DataType
$cdataTypeOf :: Scheme -> DataType
toConstr :: Scheme -> Constr
$ctoConstr :: Scheme -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scheme
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scheme
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scheme -> c Scheme
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scheme -> c Scheme
$cp1Data :: Typeable Scheme
Data, Typeable)

-- | 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.
data PathItem = PathItem
  { -- | A definition of a GET operation on this path.
    PathItem -> Maybe Operation
_pathItemGet :: Maybe Operation

    -- | A definition of a PUT operation on this path.
  , PathItem -> Maybe Operation
_pathItemPut :: Maybe Operation

    -- | A definition of a POST operation on this path.
  , PathItem -> Maybe Operation
_pathItemPost :: Maybe Operation

    -- | A definition of a DELETE operation on this path.
  , PathItem -> Maybe Operation
_pathItemDelete :: Maybe Operation

    -- | A definition of a OPTIONS operation on this path.
  , PathItem -> Maybe Operation
_pathItemOptions :: Maybe Operation

    -- | A definition of a HEAD operation on this path.
  , PathItem -> Maybe Operation
_pathItemHead :: Maybe Operation

    -- | A definition of a PATCH operation on this path.
  , PathItem -> Maybe Operation
_pathItemPatch :: Maybe Operation

    -- | A list of parameters that are applicable for all the operations described under this path.
    -- These parameters can be overridden at the operation level, but cannot be removed there.
    -- The list MUST NOT include duplicated parameters.
    -- A unique parameter is defined by a combination of a name and location.
  , PathItem -> [Referenced Param]
_pathItemParameters :: [Referenced Param]
  } deriving (PathItem -> PathItem -> Bool
(PathItem -> PathItem -> Bool)
-> (PathItem -> PathItem -> Bool) -> Eq PathItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathItem -> PathItem -> Bool
$c/= :: PathItem -> PathItem -> Bool
== :: PathItem -> PathItem -> Bool
$c== :: PathItem -> PathItem -> Bool
Eq, Int -> PathItem -> ShowS
[PathItem] -> ShowS
PathItem -> FilePath
(Int -> PathItem -> ShowS)
-> (PathItem -> FilePath) -> ([PathItem] -> ShowS) -> Show PathItem
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PathItem] -> ShowS
$cshowList :: [PathItem] -> ShowS
show :: PathItem -> FilePath
$cshow :: PathItem -> FilePath
showsPrec :: Int -> PathItem -> ShowS
$cshowsPrec :: Int -> PathItem -> ShowS
Show, (forall x. PathItem -> Rep PathItem x)
-> (forall x. Rep PathItem x -> PathItem) -> Generic PathItem
forall x. Rep PathItem x -> PathItem
forall x. PathItem -> Rep PathItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathItem x -> PathItem
$cfrom :: forall x. PathItem -> Rep PathItem x
Generic, Typeable PathItem
DataType
Constr
Typeable PathItem =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> PathItem -> c PathItem)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c PathItem)
-> (PathItem -> Constr)
-> (PathItem -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c PathItem))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem))
-> ((forall b. Data b => b -> b) -> PathItem -> PathItem)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> PathItem -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> PathItem -> r)
-> (forall u. (forall d. Data d => d -> u) -> PathItem -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> Data PathItem
PathItem -> DataType
PathItem -> Constr
(forall b. Data b => b -> b) -> PathItem -> PathItem
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathItem)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem)
$cPathItem :: Constr
$tPathItem :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PathItem -> m PathItem
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
gmapMp :: (forall d. Data d => d -> m d) -> PathItem -> m PathItem
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
gmapM :: (forall d. Data d => d -> m d) -> PathItem -> m PathItem
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
gmapQi :: Int -> (forall d. Data d => d -> u) -> PathItem -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
gmapQ :: (forall d. Data d => d -> u) -> PathItem -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
gmapT :: (forall b. Data b => b -> b) -> PathItem -> PathItem
$cgmapT :: (forall b. Data b => b -> b) -> PathItem -> PathItem
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PathItem)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathItem)
dataTypeOf :: PathItem -> DataType
$cdataTypeOf :: PathItem -> DataType
toConstr :: PathItem -> Constr
$ctoConstr :: PathItem -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
$cp1Data :: Typeable PathItem
Data, Typeable)

-- | Describes a single API operation on a path.
data Operation = Operation
  { -- | A list of tags for API documentation control.
    -- Tags can be used for logical grouping of operations by resources or any other qualifier.
    Operation -> InsOrdHashSet Text
_operationTags :: InsOrdHashSet TagName

    -- | A short summary of what the operation does.
    -- For maximum readability in the swagger-ui, this field SHOULD be less than 120 characters.
  , Operation -> Maybe Text
_operationSummary :: Maybe Text

    -- | A verbose explanation of the operation behavior.
    -- GFM syntax can be used for rich text representation.
  , Operation -> Maybe Text
_operationDescription :: Maybe Text

    -- | Additional external documentation for this operation.
  , Operation -> Maybe ExternalDocs
_operationExternalDocs :: Maybe ExternalDocs

    -- | 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.
  , Operation -> Maybe Text
_operationOperationId :: Maybe Text

    -- | A list of MIME types the operation can consume.
    -- This overrides the @'consumes'@.
    -- @Just []@ MAY be used to clear the global definition.
  , Operation -> Maybe MimeList
_operationConsumes :: Maybe MimeList

    -- | A list of MIME types the operation can produce.
    -- This overrides the @'produces'@.
    -- @Just []@ MAY be used to clear the global definition.
  , Operation -> Maybe MimeList
_operationProduces :: Maybe MimeList

    -- | 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.
  , Operation -> [Referenced Param]
_operationParameters :: [Referenced Param]

    -- | The list of possible responses as they are returned from executing this operation.
  , Operation -> Responses
_operationResponses :: Responses

    -- | The transfer protocol for the operation.
    -- The value overrides @'schemes'@.
  , Operation -> Maybe [Scheme]
_operationSchemes :: Maybe [Scheme]

    -- | Declares this operation to be deprecated.
    -- Usage of the declared operation should be refrained.
    -- Default value is @False@.
  , Operation -> Maybe Bool
_operationDeprecated :: Maybe Bool

    -- | 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.
  , Operation -> [SecurityRequirement]
_operationSecurity :: [SecurityRequirement]
  } deriving (Operation -> Operation -> Bool
(Operation -> Operation -> Bool)
-> (Operation -> Operation -> Bool) -> Eq Operation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Operation -> Operation -> Bool
$c/= :: Operation -> Operation -> Bool
== :: Operation -> Operation -> Bool
$c== :: Operation -> Operation -> Bool
Eq, Int -> Operation -> ShowS
[Operation] -> ShowS
Operation -> FilePath
(Int -> Operation -> ShowS)
-> (Operation -> FilePath)
-> ([Operation] -> ShowS)
-> Show Operation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Operation] -> ShowS
$cshowList :: [Operation] -> ShowS
show :: Operation -> FilePath
$cshow :: Operation -> FilePath
showsPrec :: Int -> Operation -> ShowS
$cshowsPrec :: Int -> Operation -> ShowS
Show, (forall x. Operation -> Rep Operation x)
-> (forall x. Rep Operation x -> Operation) -> Generic Operation
forall x. Rep Operation x -> Operation
forall x. Operation -> Rep Operation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Operation x -> Operation
$cfrom :: forall x. Operation -> Rep Operation x
Generic, Typeable Operation
DataType
Constr
Typeable Operation =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Operation -> c Operation)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Operation)
-> (Operation -> Constr)
-> (Operation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Operation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation))
-> ((forall b. Data b => b -> b) -> Operation -> Operation)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Operation -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Operation -> r)
-> (forall u. (forall d. Data d => d -> u) -> Operation -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Operation -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Operation -> m Operation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Operation -> m Operation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Operation -> m Operation)
-> Data Operation
Operation -> DataType
Operation -> Constr
(forall b. Data b => b -> b) -> Operation -> Operation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
forall u. (forall d. Data d => d -> u) -> Operation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation)
$cOperation :: Constr
$tOperation :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Operation -> m Operation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
gmapMp :: (forall d. Data d => d -> m d) -> Operation -> m Operation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
gmapM :: (forall d. Data d => d -> m d) -> Operation -> m Operation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
gmapQi :: Int -> (forall d. Data d => d -> u) -> Operation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
gmapQ :: (forall d. Data d => d -> u) -> Operation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Operation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
gmapT :: (forall b. Data b => b -> b) -> Operation -> Operation
$cgmapT :: (forall b. Data b => b -> b) -> Operation -> Operation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Operation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operation)
dataTypeOf :: Operation -> DataType
$cdataTypeOf :: Operation -> DataType
toConstr :: Operation -> Constr
$ctoConstr :: Operation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
$cp1Data :: Typeable Operation
Data, Typeable)

newtype MimeList = MimeList { MimeList -> [MediaType]
getMimeList :: [MediaType] }
  deriving (MimeList -> MimeList -> Bool
(MimeList -> MimeList -> Bool)
-> (MimeList -> MimeList -> Bool) -> Eq MimeList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MimeList -> MimeList -> Bool
$c/= :: MimeList -> MimeList -> Bool
== :: MimeList -> MimeList -> Bool
$c== :: MimeList -> MimeList -> Bool
Eq, Int -> MimeList -> ShowS
[MimeList] -> ShowS
MimeList -> FilePath
(Int -> MimeList -> ShowS)
-> (MimeList -> FilePath) -> ([MimeList] -> ShowS) -> Show MimeList
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MimeList] -> ShowS
$cshowList :: [MimeList] -> ShowS
show :: MimeList -> FilePath
$cshow :: MimeList -> FilePath
showsPrec :: Int -> MimeList -> ShowS
$cshowsPrec :: Int -> MimeList -> ShowS
Show, b -> MimeList -> MimeList
NonEmpty MimeList -> MimeList
MimeList -> MimeList -> MimeList
(MimeList -> MimeList -> MimeList)
-> (NonEmpty MimeList -> MimeList)
-> (forall b. Integral b => b -> MimeList -> MimeList)
-> Semigroup MimeList
forall b. Integral b => b -> MimeList -> MimeList
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> MimeList -> MimeList
$cstimes :: forall b. Integral b => b -> MimeList -> MimeList
sconcat :: NonEmpty MimeList -> MimeList
$csconcat :: NonEmpty MimeList -> MimeList
<> :: MimeList -> MimeList -> MimeList
$c<> :: MimeList -> MimeList -> MimeList
Semigroup, Semigroup MimeList
MimeList
Semigroup MimeList =>
MimeList
-> (MimeList -> MimeList -> MimeList)
-> ([MimeList] -> MimeList)
-> Monoid MimeList
[MimeList] -> MimeList
MimeList -> MimeList -> MimeList
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [MimeList] -> MimeList
$cmconcat :: [MimeList] -> MimeList
mappend :: MimeList -> MimeList -> MimeList
$cmappend :: MimeList -> MimeList -> MimeList
mempty :: MimeList
$cmempty :: MimeList
$cp1Monoid :: Semigroup MimeList
Monoid, Typeable)

mimeListConstr :: Constr
mimeListConstr :: Constr
mimeListConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
mimeListDataType "MimeList" ["getMimeList"] Fixity
Prefix

mimeListDataType :: DataType
mimeListDataType :: DataType
mimeListDataType = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.MimeList" [Constr
mimeListConstr]

instance Data MimeList where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MimeList
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    1 -> c ([FilePath] -> MimeList) -> c MimeList
forall b r. Data b => c (b -> r) -> c r
k (([FilePath] -> MimeList) -> c ([FilePath] -> MimeList)
forall r. r -> c r
z (\xs :: [FilePath]
xs -> [MediaType] -> MimeList
MimeList ((FilePath -> MediaType) -> [FilePath] -> [MediaType]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString [FilePath]
xs)))
    _ -> FilePath -> c MimeList
forall a. HasCallStack => FilePath -> a
error (FilePath -> c MimeList) -> FilePath -> c MimeList
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type MimeList."
  toConstr :: MimeList -> Constr
toConstr (MimeList _) = Constr
mimeListConstr
  dataTypeOf :: MimeList -> DataType
dataTypeOf _ = DataType
mimeListDataType

-- | Describes a single operation parameter.
-- A unique parameter is defined by a combination of a name and location.
data Param = Param
  { -- | The name of the parameter.
    -- Parameter names are case sensitive.
    Param -> Text
_paramName :: Text

    -- | A brief description of the parameter.
    -- This could contain examples of use.
    -- GFM syntax can be used for rich text representation.
  , Param -> Maybe Text
_paramDescription :: Maybe Text

    -- | 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@.
  , Param -> Maybe Bool
_paramRequired :: Maybe Bool

    -- | Parameter schema.
  , Param -> ParamAnySchema
_paramSchema :: ParamAnySchema
  } deriving (Param -> Param -> Bool
(Param -> Param -> Bool) -> (Param -> Param -> Bool) -> Eq Param
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Param -> Param -> Bool
$c/= :: Param -> Param -> Bool
== :: Param -> Param -> Bool
$c== :: Param -> Param -> Bool
Eq, Int -> Param -> ShowS
[Param] -> ShowS
Param -> FilePath
(Int -> Param -> ShowS)
-> (Param -> FilePath) -> ([Param] -> ShowS) -> Show Param
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Param] -> ShowS
$cshowList :: [Param] -> ShowS
show :: Param -> FilePath
$cshow :: Param -> FilePath
showsPrec :: Int -> Param -> ShowS
$cshowsPrec :: Int -> Param -> ShowS
Show, (forall x. Param -> Rep Param x)
-> (forall x. Rep Param x -> Param) -> Generic Param
forall x. Rep Param x -> Param
forall x. Param -> Rep Param x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Param x -> Param
$cfrom :: forall x. Param -> Rep Param x
Generic, Typeable Param
DataType
Constr
Typeable Param =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Param -> c Param)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Param)
-> (Param -> Constr)
-> (Param -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Param))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param))
-> ((forall b. Data b => b -> b) -> Param -> Param)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r)
-> (forall u. (forall d. Data d => d -> u) -> Param -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Param -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Param -> m Param)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Param -> m Param)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Param -> m Param)
-> Data Param
Param -> DataType
Param -> Constr
(forall b. Data b => b -> b) -> Param -> Param
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
forall u. (forall d. Data d => d -> u) -> Param -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Param -> m Param
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Param)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param)
$cParam :: Constr
$tParam :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Param -> m Param
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param
gmapMp :: (forall d. Data d => d -> m d) -> Param -> m Param
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param
gmapM :: (forall d. Data d => d -> m d) -> Param -> m Param
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Param -> m Param
gmapQi :: Int -> (forall d. Data d => d -> u) -> Param -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
gmapQ :: (forall d. Data d => d -> u) -> Param -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Param -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
gmapT :: (forall b. Data b => b -> b) -> Param -> Param
$cgmapT :: (forall b. Data b => b -> b) -> Param -> Param
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Param)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Param)
dataTypeOf :: Param -> DataType
$cdataTypeOf :: Param -> DataType
toConstr :: Param -> Constr
$ctoConstr :: Param -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
$cp1Data :: Typeable Param
Data, Typeable)

data ParamAnySchema
  = ParamBody (Referenced Schema)
  | ParamOther ParamOtherSchema
  deriving (ParamAnySchema -> ParamAnySchema -> Bool
(ParamAnySchema -> ParamAnySchema -> Bool)
-> (ParamAnySchema -> ParamAnySchema -> Bool) -> Eq ParamAnySchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamAnySchema -> ParamAnySchema -> Bool
$c/= :: ParamAnySchema -> ParamAnySchema -> Bool
== :: ParamAnySchema -> ParamAnySchema -> Bool
$c== :: ParamAnySchema -> ParamAnySchema -> Bool
Eq, Int -> ParamAnySchema -> ShowS
[ParamAnySchema] -> ShowS
ParamAnySchema -> FilePath
(Int -> ParamAnySchema -> ShowS)
-> (ParamAnySchema -> FilePath)
-> ([ParamAnySchema] -> ShowS)
-> Show ParamAnySchema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ParamAnySchema] -> ShowS
$cshowList :: [ParamAnySchema] -> ShowS
show :: ParamAnySchema -> FilePath
$cshow :: ParamAnySchema -> FilePath
showsPrec :: Int -> ParamAnySchema -> ShowS
$cshowsPrec :: Int -> ParamAnySchema -> ShowS
Show, (forall x. ParamAnySchema -> Rep ParamAnySchema x)
-> (forall x. Rep ParamAnySchema x -> ParamAnySchema)
-> Generic ParamAnySchema
forall x. Rep ParamAnySchema x -> ParamAnySchema
forall x. ParamAnySchema -> Rep ParamAnySchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParamAnySchema x -> ParamAnySchema
$cfrom :: forall x. ParamAnySchema -> Rep ParamAnySchema x
Generic, Typeable ParamAnySchema
DataType
Constr
Typeable ParamAnySchema =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ParamAnySchema)
-> (ParamAnySchema -> Constr)
-> (ParamAnySchema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ParamAnySchema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ParamAnySchema))
-> ((forall b. Data b => b -> b)
    -> ParamAnySchema -> ParamAnySchema)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ParamAnySchema -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ParamAnySchema -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ParamAnySchema -> m ParamAnySchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ParamAnySchema -> m ParamAnySchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ParamAnySchema -> m ParamAnySchema)
-> Data ParamAnySchema
ParamAnySchema -> DataType
ParamAnySchema -> Constr
(forall b. Data b => b -> b) -> ParamAnySchema -> ParamAnySchema
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamAnySchema
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ParamAnySchema -> u
forall u. (forall d. Data d => d -> u) -> ParamAnySchema -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamAnySchema
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamAnySchema)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamAnySchema)
$cParamOther :: Constr
$cParamBody :: Constr
$tParamAnySchema :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
gmapMp :: (forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
gmapM :: (forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParamAnySchema -> m ParamAnySchema
gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamAnySchema -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ParamAnySchema -> u
gmapQ :: (forall d. Data d => d -> u) -> ParamAnySchema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParamAnySchema -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamAnySchema -> r
gmapT :: (forall b. Data b => b -> b) -> ParamAnySchema -> ParamAnySchema
$cgmapT :: (forall b. Data b => b -> b) -> ParamAnySchema -> ParamAnySchema
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamAnySchema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamAnySchema)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ParamAnySchema)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamAnySchema)
dataTypeOf :: ParamAnySchema -> DataType
$cdataTypeOf :: ParamAnySchema -> DataType
toConstr :: ParamAnySchema -> Constr
$ctoConstr :: ParamAnySchema -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamAnySchema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamAnySchema
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamAnySchema -> c ParamAnySchema
$cp1Data :: Typeable ParamAnySchema
Data, Typeable)

data ParamOtherSchema = ParamOtherSchema
  { -- | The location of the parameter.
    ParamOtherSchema -> ParamLocation
_paramOtherSchemaIn :: ParamLocation

    -- | Sets the ability to pass empty-valued parameters.
    -- This is valid only for either @'ParamQuery'@ or @'ParamFormData'@
    -- and allows you to send a parameter with a name only or an empty value.
    -- Default value is @False@.
  , ParamOtherSchema -> Maybe Bool
_paramOtherSchemaAllowEmptyValue :: Maybe Bool

  , ParamOtherSchema -> ParamSchema 'SwaggerKindParamOtherSchema
_paramOtherSchemaParamSchema :: ParamSchema 'SwaggerKindParamOtherSchema
  } deriving (ParamOtherSchema -> ParamOtherSchema -> Bool
(ParamOtherSchema -> ParamOtherSchema -> Bool)
-> (ParamOtherSchema -> ParamOtherSchema -> Bool)
-> Eq ParamOtherSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamOtherSchema -> ParamOtherSchema -> Bool
$c/= :: ParamOtherSchema -> ParamOtherSchema -> Bool
== :: ParamOtherSchema -> ParamOtherSchema -> Bool
$c== :: ParamOtherSchema -> ParamOtherSchema -> Bool
Eq, Int -> ParamOtherSchema -> ShowS
[ParamOtherSchema] -> ShowS
ParamOtherSchema -> FilePath
(Int -> ParamOtherSchema -> ShowS)
-> (ParamOtherSchema -> FilePath)
-> ([ParamOtherSchema] -> ShowS)
-> Show ParamOtherSchema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ParamOtherSchema] -> ShowS
$cshowList :: [ParamOtherSchema] -> ShowS
show :: ParamOtherSchema -> FilePath
$cshow :: ParamOtherSchema -> FilePath
showsPrec :: Int -> ParamOtherSchema -> ShowS
$cshowsPrec :: Int -> ParamOtherSchema -> ShowS
Show, (forall x. ParamOtherSchema -> Rep ParamOtherSchema x)
-> (forall x. Rep ParamOtherSchema x -> ParamOtherSchema)
-> Generic ParamOtherSchema
forall x. Rep ParamOtherSchema x -> ParamOtherSchema
forall x. ParamOtherSchema -> Rep ParamOtherSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParamOtherSchema x -> ParamOtherSchema
$cfrom :: forall x. ParamOtherSchema -> Rep ParamOtherSchema x
Generic, Typeable, Typeable ParamOtherSchema
DataType
Constr
Typeable ParamOtherSchema =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ParamOtherSchema)
-> (ParamOtherSchema -> Constr)
-> (ParamOtherSchema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ParamOtherSchema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ParamOtherSchema))
-> ((forall b. Data b => b -> b)
    -> ParamOtherSchema -> ParamOtherSchema)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ParamOtherSchema -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ParamOtherSchema -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ParamOtherSchema -> m ParamOtherSchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ParamOtherSchema -> m ParamOtherSchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ParamOtherSchema -> m ParamOtherSchema)
-> Data ParamOtherSchema
ParamOtherSchema -> DataType
ParamOtherSchema -> Constr
(forall b. Data b => b -> b)
-> ParamOtherSchema -> ParamOtherSchema
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamOtherSchema
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ParamOtherSchema -> u
forall u. (forall d. Data d => d -> u) -> ParamOtherSchema -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamOtherSchema
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamOtherSchema)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamOtherSchema)
$cParamOtherSchema :: Constr
$tParamOtherSchema :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
gmapMp :: (forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
gmapM :: (forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParamOtherSchema -> m ParamOtherSchema
gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamOtherSchema -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ParamOtherSchema -> u
gmapQ :: (forall d. Data d => d -> u) -> ParamOtherSchema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParamOtherSchema -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamOtherSchema -> r
gmapT :: (forall b. Data b => b -> b)
-> ParamOtherSchema -> ParamOtherSchema
$cgmapT :: (forall b. Data b => b -> b)
-> ParamOtherSchema -> ParamOtherSchema
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamOtherSchema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamOtherSchema)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ParamOtherSchema)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamOtherSchema)
dataTypeOf :: ParamOtherSchema -> DataType
$cdataTypeOf :: ParamOtherSchema -> DataType
toConstr :: ParamOtherSchema -> Constr
$ctoConstr :: ParamOtherSchema -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamOtherSchema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamOtherSchema
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamOtherSchema -> c ParamOtherSchema
$cp1Data :: Typeable ParamOtherSchema
Data)

-- | 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 <http://swagger.io/specification/#itemsObject Items Object>.
--
-- @'SwaggerItemsObject'@ should be used to specify homogenous array @'Schema'@s.
--
-- @'SwaggerItemsArray'@ should be used to specify tuple @'Schema'@s.
data SwaggerItems t where
  SwaggerItemsPrimitive :: Maybe (CollectionFormat k) -> ParamSchema k-> SwaggerItems k
  SwaggerItemsObject    :: Referenced Schema   -> SwaggerItems 'SwaggerKindSchema
  SwaggerItemsArray     :: [Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
  deriving (Typeable)

deriving instance Eq (SwaggerItems t)
deriving instance Show (SwaggerItems t)
--deriving instance Typeable (SwaggerItems t)

swaggerItemsPrimitiveConstr :: Constr
swaggerItemsPrimitiveConstr :: Constr
swaggerItemsPrimitiveConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
swaggerItemsDataType "SwaggerItemsPrimitive" [] Fixity
Prefix

swaggerItemsObjectConstr :: Constr
swaggerItemsObjectConstr :: Constr
swaggerItemsObjectConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
swaggerItemsDataType "SwaggerItemsObject" [] Fixity
Prefix

swaggerItemsArrayConstr :: Constr
swaggerItemsArrayConstr :: Constr
swaggerItemsArrayConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
swaggerItemsDataType "SwaggerItemsArray" [] Fixity
Prefix

swaggerItemsDataType :: DataType
swaggerItemsDataType :: DataType
swaggerItemsDataType = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.SwaggerItems" [Constr
swaggerItemsPrimitiveConstr]

-- Note: unfortunately we have to write these Data instances by hand,
-- to get better contexts / avoid duplicate name when using standalone deriving

instance Data t => Data (SwaggerItems ('SwaggerKindNormal t)) where
  -- TODO: define gfoldl
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerItems ('SwaggerKindNormal t))
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    1 -> c (ParamSchema ('SwaggerKindNormal t)
   -> SwaggerItems ('SwaggerKindNormal t))
-> c (SwaggerItems ('SwaggerKindNormal t))
forall b r. Data b => c (b -> r) -> c r
k (c (Maybe (CollectionFormat ('SwaggerKindNormal t))
   -> ParamSchema ('SwaggerKindNormal t)
   -> SwaggerItems ('SwaggerKindNormal t))
-> c (ParamSchema ('SwaggerKindNormal t)
      -> SwaggerItems ('SwaggerKindNormal t))
forall b r. Data b => c (b -> r) -> c r
k ((Maybe (CollectionFormat ('SwaggerKindNormal t))
 -> ParamSchema ('SwaggerKindNormal t)
 -> SwaggerItems ('SwaggerKindNormal t))
-> c (Maybe (CollectionFormat ('SwaggerKindNormal t))
      -> ParamSchema ('SwaggerKindNormal t)
      -> SwaggerItems ('SwaggerKindNormal t))
forall r. r -> c r
z Maybe (CollectionFormat ('SwaggerKindNormal t))
-> ParamSchema ('SwaggerKindNormal t)
-> SwaggerItems ('SwaggerKindNormal t)
forall (k :: SwaggerKind *).
Maybe (CollectionFormat k) -> ParamSchema k -> SwaggerItems k
SwaggerItemsPrimitive))
    _ -> FilePath -> c (SwaggerItems ('SwaggerKindNormal t))
forall a. HasCallStack => FilePath -> a
error (FilePath -> c (SwaggerItems ('SwaggerKindNormal t)))
-> FilePath -> c (SwaggerItems ('SwaggerKindNormal t))
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type (SwaggerItems t)."
  toConstr :: SwaggerItems ('SwaggerKindNormal t) -> Constr
toConstr _ = Constr
swaggerItemsPrimitiveConstr
  dataTypeOf :: SwaggerItems ('SwaggerKindNormal t) -> DataType
dataTypeOf _ = DataType
swaggerItemsDataType

-- SwaggerItems SwaggerKindParamOtherSchema can be constructed using SwaggerItemsPrimitive only
instance Data (SwaggerItems 'SwaggerKindParamOtherSchema) where
  -- TODO: define gfoldl
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerItems 'SwaggerKindParamOtherSchema)
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    1 -> c (ParamSchema 'SwaggerKindParamOtherSchema
   -> SwaggerItems 'SwaggerKindParamOtherSchema)
-> c (SwaggerItems 'SwaggerKindParamOtherSchema)
forall b r. Data b => c (b -> r) -> c r
k (c (Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
   -> ParamSchema 'SwaggerKindParamOtherSchema
   -> SwaggerItems 'SwaggerKindParamOtherSchema)
-> c (ParamSchema 'SwaggerKindParamOtherSchema
      -> SwaggerItems 'SwaggerKindParamOtherSchema)
forall b r. Data b => c (b -> r) -> c r
k ((Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
 -> ParamSchema 'SwaggerKindParamOtherSchema
 -> SwaggerItems 'SwaggerKindParamOtherSchema)
-> c (Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
      -> ParamSchema 'SwaggerKindParamOtherSchema
      -> SwaggerItems 'SwaggerKindParamOtherSchema)
forall r. r -> c r
z Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
-> ParamSchema 'SwaggerKindParamOtherSchema
-> SwaggerItems 'SwaggerKindParamOtherSchema
forall (k :: SwaggerKind *).
Maybe (CollectionFormat k) -> ParamSchema k -> SwaggerItems k
SwaggerItemsPrimitive))
    _ -> FilePath -> c (SwaggerItems 'SwaggerKindParamOtherSchema)
forall a. HasCallStack => FilePath -> a
error (FilePath -> c (SwaggerItems 'SwaggerKindParamOtherSchema))
-> FilePath -> c (SwaggerItems 'SwaggerKindParamOtherSchema)
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type (SwaggerItems SwaggerKindParamOtherSchema)."
  toConstr :: SwaggerItems 'SwaggerKindParamOtherSchema -> Constr
toConstr _ = Constr
swaggerItemsPrimitiveConstr
  dataTypeOf :: SwaggerItems 'SwaggerKindParamOtherSchema -> DataType
dataTypeOf _ = DataType
swaggerItemsDataType

instance Data (SwaggerItems 'SwaggerKindSchema) where
  gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SwaggerItems 'SwaggerKindSchema
-> c (SwaggerItems 'SwaggerKindSchema)
gfoldl _ _ (SwaggerItemsPrimitive _ _) = FilePath -> c (SwaggerItems 'SwaggerKindSchema)
forall a. HasCallStack => FilePath -> a
error " Data.Data.gfoldl: Constructor SwaggerItemsPrimitive used to construct SwaggerItems SwaggerKindSchema"
  gfoldl k :: forall d b. Data d => c (d -> b) -> d -> c b
k z :: forall g. g -> c g
z (SwaggerItemsObject ref :: Referenced Schema
ref)    = (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
-> c (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
forall g. g -> c g
z Referenced Schema -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsObject c (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
-> Referenced Schema -> c (SwaggerItems 'SwaggerKindSchema)
forall d b. Data d => c (d -> b) -> d -> c b
`k` Referenced Schema
ref
  gfoldl k :: forall d b. Data d => c (d -> b) -> d -> c b
k z :: forall g. g -> c g
z (SwaggerItemsArray ref :: [Referenced Schema]
ref)     = ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
-> c ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
forall g. g -> c g
z [Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsArray c ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
-> [Referenced Schema] -> c (SwaggerItems 'SwaggerKindSchema)
forall d b. Data d => c (d -> b) -> d -> c b
`k` [Referenced Schema]
ref

  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerItems 'SwaggerKindSchema)
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    2 -> c (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
-> c (SwaggerItems 'SwaggerKindSchema)
forall b r. Data b => c (b -> r) -> c r
k ((Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
-> c (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
forall r. r -> c r
z Referenced Schema -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsObject)
    3 -> c ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
-> c (SwaggerItems 'SwaggerKindSchema)
forall b r. Data b => c (b -> r) -> c r
k (([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
-> c ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
forall r. r -> c r
z [Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsArray)
    _ -> FilePath -> c (SwaggerItems 'SwaggerKindSchema)
forall a. HasCallStack => FilePath -> a
error (FilePath -> c (SwaggerItems 'SwaggerKindSchema))
-> FilePath -> c (SwaggerItems 'SwaggerKindSchema)
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type (SwaggerItems SwaggerKindSchema)."

  toConstr :: SwaggerItems 'SwaggerKindSchema -> Constr
toConstr (SwaggerItemsPrimitive _ _) = FilePath -> Constr
forall a. HasCallStack => FilePath -> a
error "Not supported"
  toConstr (SwaggerItemsObject _)      = Constr
swaggerItemsObjectConstr
  toConstr (SwaggerItemsArray _)       = Constr
swaggerItemsArrayConstr

  dataTypeOf :: SwaggerItems 'SwaggerKindSchema -> DataType
dataTypeOf _ = DataType
swaggerItemsDataType

-- | Type used as a kind to avoid overlapping instances.
data SwaggerKind t
    = SwaggerKindNormal t
    | SwaggerKindParamOtherSchema
    | SwaggerKindSchema
    deriving (Typeable)

deriving instance Typeable 'SwaggerKindNormal
deriving instance Typeable 'SwaggerKindParamOtherSchema
deriving instance Typeable 'SwaggerKindSchema

type family SwaggerKindType (k :: SwaggerKind *) :: *
type instance SwaggerKindType ('SwaggerKindNormal t) = t
type instance SwaggerKindType 'SwaggerKindSchema = Schema
type instance SwaggerKindType 'SwaggerKindParamOtherSchema = ParamOtherSchema

data SwaggerType t where
  SwaggerString   :: SwaggerType t
  SwaggerNumber   :: SwaggerType t
  SwaggerInteger  :: SwaggerType t
  SwaggerBoolean  :: SwaggerType t
  SwaggerArray    :: SwaggerType t
  SwaggerFile     :: SwaggerType 'SwaggerKindParamOtherSchema
  SwaggerNull     :: SwaggerType 'SwaggerKindSchema
  SwaggerObject   :: SwaggerType 'SwaggerKindSchema
  deriving (Typeable)

deriving instance Eq (SwaggerType t)
deriving instance Show (SwaggerType t)

swaggerTypeConstr :: Data (SwaggerType t) => SwaggerType t -> Constr
swaggerTypeConstr :: SwaggerType t -> Constr
swaggerTypeConstr t :: SwaggerType t
t = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr (SwaggerType t -> DataType
forall a. Data a => a -> DataType
dataTypeOf SwaggerType t
t) (SwaggerType t -> FilePath
forall a. Show a => a -> FilePath
show SwaggerType t
t) [] Fixity
Prefix

swaggerTypeDataType :: {- Data (SwaggerType t) => -} SwaggerType t -> DataType
swaggerTypeDataType :: SwaggerType t -> DataType
swaggerTypeDataType _ = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.SwaggerType" [Constr]
swaggerTypeConstrs

swaggerCommonTypes :: [SwaggerType k]
swaggerCommonTypes :: [SwaggerType k]
swaggerCommonTypes = [SwaggerType k
forall (t :: SwaggerKind *). SwaggerType t
SwaggerString, SwaggerType k
forall (t :: SwaggerKind *). SwaggerType t
SwaggerNumber, SwaggerType k
forall (t :: SwaggerKind *). SwaggerType t
SwaggerInteger, SwaggerType k
forall (t :: SwaggerKind *). SwaggerType t
SwaggerBoolean, SwaggerType k
forall (t :: SwaggerKind *). SwaggerType t
SwaggerArray]

swaggerParamTypes :: [SwaggerType 'SwaggerKindParamOtherSchema]
swaggerParamTypes :: [SwaggerType 'SwaggerKindParamOtherSchema]
swaggerParamTypes = [SwaggerType 'SwaggerKindParamOtherSchema]
forall (k :: SwaggerKind *). [SwaggerType k]
swaggerCommonTypes [SwaggerType 'SwaggerKindParamOtherSchema]
-> [SwaggerType 'SwaggerKindParamOtherSchema]
-> [SwaggerType 'SwaggerKindParamOtherSchema]
forall a. [a] -> [a] -> [a]
++ [SwaggerType 'SwaggerKindParamOtherSchema
SwaggerFile]

swaggerSchemaTypes :: [SwaggerType 'SwaggerKindSchema]
swaggerSchemaTypes :: [SwaggerType 'SwaggerKindSchema]
swaggerSchemaTypes = [SwaggerType 'SwaggerKindSchema]
forall (k :: SwaggerKind *). [SwaggerType k]
swaggerCommonTypes [SwaggerType 'SwaggerKindSchema]
-> [SwaggerType 'SwaggerKindSchema]
-> [SwaggerType 'SwaggerKindSchema]
forall a. [a] -> [a] -> [a]
++ [FilePath -> SwaggerType 'SwaggerKindSchema
forall a. HasCallStack => FilePath -> a
error "SwaggerFile is invalid SwaggerType Schema", SwaggerType 'SwaggerKindSchema
SwaggerNull, SwaggerType 'SwaggerKindSchema
SwaggerObject]

swaggerTypeConstrs :: [Constr]
swaggerTypeConstrs :: [Constr]
swaggerTypeConstrs = (SwaggerType 'SwaggerKindSchema -> Constr)
-> [SwaggerType 'SwaggerKindSchema] -> [Constr]
forall a b. (a -> b) -> [a] -> [b]
map SwaggerType 'SwaggerKindSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr ([SwaggerType 'SwaggerKindSchema]
forall (k :: SwaggerKind *). [SwaggerType k]
swaggerCommonTypes :: [SwaggerType 'SwaggerKindSchema])
  [Constr] -> [Constr] -> [Constr]
forall a. [a] -> [a] -> [a]
++ [SwaggerType 'SwaggerKindParamOtherSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr SwaggerType 'SwaggerKindParamOtherSchema
SwaggerFile, SwaggerType 'SwaggerKindSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr SwaggerType 'SwaggerKindSchema
SwaggerNull, SwaggerType 'SwaggerKindSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr SwaggerType 'SwaggerKindSchema
SwaggerObject]

instance Typeable t => Data (SwaggerType ('SwaggerKindNormal t)) where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType ('SwaggerKindNormal t))
gunfold = FilePath
-> [SwaggerType ('SwaggerKindNormal t)]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType ('SwaggerKindNormal t))
forall a (c :: * -> *).
FilePath
-> [a]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c a
gunfoldEnum "SwaggerType" [SwaggerType ('SwaggerKindNormal t)]
forall (k :: SwaggerKind *). [SwaggerType k]
swaggerCommonTypes
  toConstr :: SwaggerType ('SwaggerKindNormal t) -> Constr
toConstr = SwaggerType ('SwaggerKindNormal t) -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr
  dataTypeOf :: SwaggerType ('SwaggerKindNormal t) -> DataType
dataTypeOf = SwaggerType ('SwaggerKindNormal t) -> DataType
forall (t :: SwaggerKind *). SwaggerType t -> DataType
swaggerTypeDataType

instance Data (SwaggerType 'SwaggerKindParamOtherSchema) where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType 'SwaggerKindParamOtherSchema)
gunfold = FilePath
-> [SwaggerType 'SwaggerKindParamOtherSchema]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType 'SwaggerKindParamOtherSchema)
forall a (c :: * -> *).
FilePath
-> [a]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c a
gunfoldEnum "SwaggerType ParamOtherSchema" [SwaggerType 'SwaggerKindParamOtherSchema]
swaggerParamTypes
  toConstr :: SwaggerType 'SwaggerKindParamOtherSchema -> Constr
toConstr = SwaggerType 'SwaggerKindParamOtherSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr
  dataTypeOf :: SwaggerType 'SwaggerKindParamOtherSchema -> DataType
dataTypeOf = SwaggerType 'SwaggerKindParamOtherSchema -> DataType
forall (t :: SwaggerKind *). SwaggerType t -> DataType
swaggerTypeDataType

instance Data (SwaggerType 'SwaggerKindSchema) where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType 'SwaggerKindSchema)
gunfold = FilePath
-> [SwaggerType 'SwaggerKindSchema]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (SwaggerType 'SwaggerKindSchema)
forall a (c :: * -> *).
FilePath
-> [a]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c a
gunfoldEnum "SwaggerType Schema" [SwaggerType 'SwaggerKindSchema]
swaggerSchemaTypes
  toConstr :: SwaggerType 'SwaggerKindSchema -> Constr
toConstr = SwaggerType 'SwaggerKindSchema -> Constr
forall (t :: SwaggerKind *).
Data (SwaggerType t) =>
SwaggerType t -> Constr
swaggerTypeConstr
  dataTypeOf :: SwaggerType 'SwaggerKindSchema -> DataType
dataTypeOf = SwaggerType 'SwaggerKindSchema -> DataType
forall (t :: SwaggerKind *). SwaggerType t -> DataType
swaggerTypeDataType

data ParamLocation
  = -- | Parameters that are appended to the URL.
    -- For example, in @/items?id=###@, the query parameter is @id@.
    ParamQuery
    -- | Custom headers that are expected as part of the request.
  | ParamHeader
    -- | 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@.
  | ParamPath
    -- | 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>).
  | ParamFormData
  deriving (ParamLocation -> ParamLocation -> Bool
(ParamLocation -> ParamLocation -> Bool)
-> (ParamLocation -> ParamLocation -> Bool) -> Eq ParamLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamLocation -> ParamLocation -> Bool
$c/= :: ParamLocation -> ParamLocation -> Bool
== :: ParamLocation -> ParamLocation -> Bool
$c== :: ParamLocation -> ParamLocation -> Bool
Eq, Int -> ParamLocation -> ShowS
[ParamLocation] -> ShowS
ParamLocation -> FilePath
(Int -> ParamLocation -> ShowS)
-> (ParamLocation -> FilePath)
-> ([ParamLocation] -> ShowS)
-> Show ParamLocation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ParamLocation] -> ShowS
$cshowList :: [ParamLocation] -> ShowS
show :: ParamLocation -> FilePath
$cshow :: ParamLocation -> FilePath
showsPrec :: Int -> ParamLocation -> ShowS
$cshowsPrec :: Int -> ParamLocation -> ShowS
Show, (forall x. ParamLocation -> Rep ParamLocation x)
-> (forall x. Rep ParamLocation x -> ParamLocation)
-> Generic ParamLocation
forall x. Rep ParamLocation x -> ParamLocation
forall x. ParamLocation -> Rep ParamLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParamLocation x -> ParamLocation
$cfrom :: forall x. ParamLocation -> Rep ParamLocation x
Generic, Typeable ParamLocation
DataType
Constr
Typeable ParamLocation =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ParamLocation -> c ParamLocation)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ParamLocation)
-> (ParamLocation -> Constr)
-> (ParamLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ParamLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ParamLocation))
-> ((forall b. Data b => b -> b) -> ParamLocation -> ParamLocation)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamLocation -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ParamLocation -> r)
-> (forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ParamLocation -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> Data ParamLocation
ParamLocation -> DataType
ParamLocation -> Constr
(forall b. Data b => b -> b) -> ParamLocation -> ParamLocation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamLocation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation)
$cParamFormData :: Constr
$cParamPath :: Constr
$cParamHeader :: Constr
$cParamQuery :: Constr
$tParamLocation :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
gmapMp :: (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
gmapM :: (forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
gmapQ :: (forall d. Data d => d -> u) -> ParamLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
gmapT :: (forall b. Data b => b -> b) -> ParamLocation -> ParamLocation
$cgmapT :: (forall b. Data b => b -> b) -> ParamLocation -> ParamLocation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ParamLocation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamLocation)
dataTypeOf :: ParamLocation -> DataType
$cdataTypeOf :: ParamLocation -> DataType
toConstr :: ParamLocation -> Constr
$ctoConstr :: ParamLocation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
$cp1Data :: Typeable ParamLocation
Data, Typeable)

type Format = Text

-- | Determines the format of the array.
data CollectionFormat t where
  -- Comma separated values: @foo,bar@.
  CollectionCSV :: CollectionFormat t
  -- Space separated values: @foo bar@.
  CollectionSSV :: CollectionFormat t
  -- Tab separated values: @foo\\tbar@.
  CollectionTSV :: CollectionFormat t
  -- Pipe separated values: @foo|bar@.
  CollectionPipes :: CollectionFormat t
  -- Corresponds to multiple parameter instances
  -- instead of multiple values for a single instance @foo=bar&foo=baz@.
  -- This is valid only for parameters in @'ParamQuery'@ or @'ParamFormData'@.
  CollectionMulti :: CollectionFormat 'SwaggerKindParamOtherSchema
  deriving (Typeable)

deriving instance Eq (CollectionFormat t)
deriving instance Show (CollectionFormat t)

collectionFormatConstr :: CollectionFormat t -> Constr
collectionFormatConstr :: CollectionFormat t -> Constr
collectionFormatConstr cf :: CollectionFormat t
cf = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
collectionFormatDataType (CollectionFormat t -> FilePath
forall a. Show a => a -> FilePath
show CollectionFormat t
cf) [] Fixity
Prefix

collectionFormatDataType :: DataType
collectionFormatDataType :: DataType
collectionFormatDataType = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.CollectionFormat" ([Constr] -> DataType) -> [Constr] -> DataType
forall a b. (a -> b) -> a -> b
$
  (CollectionFormat Any -> Constr)
-> [CollectionFormat Any] -> [Constr]
forall a b. (a -> b) -> [a] -> [b]
map CollectionFormat Any -> Constr
forall (t :: SwaggerKind *). CollectionFormat t -> Constr
collectionFormatConstr [CollectionFormat Any]
forall (t :: SwaggerKind *). [CollectionFormat t]
collectionCommonFormats

collectionCommonFormats :: [CollectionFormat t]
collectionCommonFormats :: [CollectionFormat t]
collectionCommonFormats = [ CollectionFormat t
forall (t :: SwaggerKind *). CollectionFormat t
CollectionCSV, CollectionFormat t
forall (t :: SwaggerKind *). CollectionFormat t
CollectionSSV, CollectionFormat t
forall (t :: SwaggerKind *). CollectionFormat t
CollectionTSV, CollectionFormat t
forall (t :: SwaggerKind *). CollectionFormat t
CollectionPipes ]

instance Data t => Data (CollectionFormat ('SwaggerKindNormal t)) where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (CollectionFormat ('SwaggerKindNormal t))
gunfold = FilePath
-> [CollectionFormat ('SwaggerKindNormal t)]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (CollectionFormat ('SwaggerKindNormal t))
forall a (c :: * -> *).
FilePath
-> [a]
-> (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c a
gunfoldEnum "CollectionFormat" [CollectionFormat ('SwaggerKindNormal t)]
forall (t :: SwaggerKind *). [CollectionFormat t]
collectionCommonFormats
  toConstr :: CollectionFormat ('SwaggerKindNormal t) -> Constr
toConstr = CollectionFormat ('SwaggerKindNormal t) -> Constr
forall (t :: SwaggerKind *). CollectionFormat t -> Constr
collectionFormatConstr
  dataTypeOf :: CollectionFormat ('SwaggerKindNormal t) -> DataType
dataTypeOf _ = DataType
collectionFormatDataType

deriving instance Data (CollectionFormat 'SwaggerKindParamOtherSchema)

type ParamName = Text

data Schema = Schema
  { Schema -> Maybe Text
_schemaTitle :: Maybe Text
  , Schema -> Maybe Text
_schemaDescription :: Maybe Text
  , Schema -> [Text]
_schemaRequired :: [ParamName]

  , Schema -> Maybe [Referenced Schema]
_schemaAllOf :: Maybe [Referenced Schema]
  , Schema -> InsOrdHashMap Text (Referenced Schema)
_schemaProperties :: InsOrdHashMap Text (Referenced Schema)
  , Schema -> Maybe AdditionalProperties
_schemaAdditionalProperties :: Maybe AdditionalProperties

  , Schema -> Maybe Text
_schemaDiscriminator :: Maybe Text
  , Schema -> Maybe Bool
_schemaReadOnly :: Maybe Bool
  , Schema -> Maybe Xml
_schemaXml :: Maybe Xml
  , Schema -> Maybe ExternalDocs
_schemaExternalDocs :: Maybe ExternalDocs
  , Schema -> Maybe Value
_schemaExample :: Maybe Value

  , Schema -> Maybe Integer
_schemaMaxProperties :: Maybe Integer
  , Schema -> Maybe Integer
_schemaMinProperties :: Maybe Integer

  , Schema -> ParamSchema 'SwaggerKindSchema
_schemaParamSchema :: ParamSchema 'SwaggerKindSchema
  } deriving (Schema -> Schema -> Bool
(Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool) -> Eq Schema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Schema -> Schema -> Bool
$c/= :: Schema -> Schema -> Bool
== :: Schema -> Schema -> Bool
$c== :: Schema -> Schema -> Bool
Eq, Int -> Schema -> ShowS
[Schema] -> ShowS
Schema -> FilePath
(Int -> Schema -> ShowS)
-> (Schema -> FilePath) -> ([Schema] -> ShowS) -> Show Schema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Schema] -> ShowS
$cshowList :: [Schema] -> ShowS
show :: Schema -> FilePath
$cshow :: Schema -> FilePath
showsPrec :: Int -> Schema -> ShowS
$cshowsPrec :: Int -> Schema -> ShowS
Show, (forall x. Schema -> Rep Schema x)
-> (forall x. Rep Schema x -> Schema) -> Generic Schema
forall x. Rep Schema x -> Schema
forall x. Schema -> Rep Schema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Schema x -> Schema
$cfrom :: forall x. Schema -> Rep Schema x
Generic, Typeable Schema
DataType
Constr
Typeable Schema =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Schema -> c Schema)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Schema)
-> (Schema -> Constr)
-> (Schema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Schema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema))
-> ((forall b. Data b => b -> b) -> Schema -> Schema)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Schema -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Schema -> r)
-> (forall u. (forall d. Data d => d -> u) -> Schema -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Schema -> m Schema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Schema -> m Schema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Schema -> m Schema)
-> Data Schema
Schema -> DataType
Schema -> Constr
(forall b. Data b => b -> b) -> Schema -> Schema
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
forall u. (forall d. Data d => d -> u) -> Schema -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Schema)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema)
$cSchema :: Constr
$tSchema :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Schema -> m Schema
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
gmapMp :: (forall d. Data d => d -> m d) -> Schema -> m Schema
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
gmapM :: (forall d. Data d => d -> m d) -> Schema -> m Schema
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
gmapQi :: Int -> (forall d. Data d => d -> u) -> Schema -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
gmapQ :: (forall d. Data d => d -> u) -> Schema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Schema -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
gmapT :: (forall b. Data b => b -> b) -> Schema -> Schema
$cgmapT :: (forall b. Data b => b -> b) -> Schema -> Schema
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Schema)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Schema)
dataTypeOf :: Schema -> DataType
$cdataTypeOf :: Schema -> DataType
toConstr :: Schema -> Constr
$ctoConstr :: Schema -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
$cp1Data :: Typeable Schema
Data, Typeable)

-- | A @'Schema'@ with an optional name.
-- This name can be used in references.
data NamedSchema = NamedSchema
  { NamedSchema -> Maybe Text
_namedSchemaName :: Maybe Text
  , NamedSchema -> Schema
_namedSchemaSchema :: Schema
  } deriving (NamedSchema -> NamedSchema -> Bool
(NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool) -> Eq NamedSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NamedSchema -> NamedSchema -> Bool
$c/= :: NamedSchema -> NamedSchema -> Bool
== :: NamedSchema -> NamedSchema -> Bool
$c== :: NamedSchema -> NamedSchema -> Bool
Eq, Int -> NamedSchema -> ShowS
[NamedSchema] -> ShowS
NamedSchema -> FilePath
(Int -> NamedSchema -> ShowS)
-> (NamedSchema -> FilePath)
-> ([NamedSchema] -> ShowS)
-> Show NamedSchema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [NamedSchema] -> ShowS
$cshowList :: [NamedSchema] -> ShowS
show :: NamedSchema -> FilePath
$cshow :: NamedSchema -> FilePath
showsPrec :: Int -> NamedSchema -> ShowS
$cshowsPrec :: Int -> NamedSchema -> ShowS
Show, (forall x. NamedSchema -> Rep NamedSchema x)
-> (forall x. Rep NamedSchema x -> NamedSchema)
-> Generic NamedSchema
forall x. Rep NamedSchema x -> NamedSchema
forall x. NamedSchema -> Rep NamedSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NamedSchema x -> NamedSchema
$cfrom :: forall x. NamedSchema -> Rep NamedSchema x
Generic, Typeable NamedSchema
DataType
Constr
Typeable NamedSchema =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> NamedSchema -> c NamedSchema)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NamedSchema)
-> (NamedSchema -> Constr)
-> (NamedSchema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NamedSchema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c NamedSchema))
-> ((forall b. Data b => b -> b) -> NamedSchema -> NamedSchema)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NamedSchema -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NamedSchema -> r)
-> (forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NamedSchema -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> Data NamedSchema
NamedSchema -> DataType
NamedSchema -> Constr
(forall b. Data b => b -> b) -> NamedSchema -> NamedSchema
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NamedSchema)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema)
$cNamedSchema :: Constr
$tNamedSchema :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
gmapMp :: (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
gmapM :: (forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
gmapQ :: (forall d. Data d => d -> u) -> NamedSchema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
gmapT :: (forall b. Data b => b -> b) -> NamedSchema -> NamedSchema
$cgmapT :: (forall b. Data b => b -> b) -> NamedSchema -> NamedSchema
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NamedSchema)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NamedSchema)
dataTypeOf :: NamedSchema -> DataType
$cdataTypeOf :: NamedSchema -> DataType
toConstr :: NamedSchema -> Constr
$ctoConstr :: NamedSchema -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
$cp1Data :: Typeable NamedSchema
Data, Typeable)

-- | Regex pattern for @string@ type.
type Pattern = Text

data ParamSchema (t :: SwaggerKind *) = ParamSchema
  { -- | Declares the value of the parameter that the server will use if none is provided,
    -- for example a @"count"@ to control the number of results per page might default to @100@
    -- if not supplied by the client in the request.
    -- (Note: "default" has no meaning for required parameters.)
    -- Unlike JSON Schema this value MUST conform to the defined type for this parameter.
    ParamSchema t -> Maybe Value
_paramSchemaDefault :: Maybe Value

  , ParamSchema t -> Maybe (SwaggerType t)
_paramSchemaType :: Maybe (SwaggerType t)
  , ParamSchema t -> Maybe Text
_paramSchemaFormat :: Maybe Format
  , ParamSchema t -> Maybe (SwaggerItems t)
_paramSchemaItems :: Maybe (SwaggerItems t)
  , ParamSchema t -> Maybe Scientific
_paramSchemaMaximum :: Maybe Scientific
  , ParamSchema t -> Maybe Bool
_paramSchemaExclusiveMaximum :: Maybe Bool
  , ParamSchema t -> Maybe Scientific
_paramSchemaMinimum :: Maybe Scientific
  , ParamSchema t -> Maybe Bool
_paramSchemaExclusiveMinimum :: Maybe Bool
  , ParamSchema t -> Maybe Integer
_paramSchemaMaxLength :: Maybe Integer
  , ParamSchema t -> Maybe Integer
_paramSchemaMinLength :: Maybe Integer
  , ParamSchema t -> Maybe Text
_paramSchemaPattern :: Maybe Pattern
  , ParamSchema t -> Maybe Integer
_paramSchemaMaxItems :: Maybe Integer
  , ParamSchema t -> Maybe Integer
_paramSchemaMinItems :: Maybe Integer
  , ParamSchema t -> Maybe Bool
_paramSchemaUniqueItems :: Maybe Bool
  , ParamSchema t -> Maybe [Value]
_paramSchemaEnum :: Maybe [Value]
  , ParamSchema t -> Maybe Scientific
_paramSchemaMultipleOf :: Maybe Scientific
  } deriving (ParamSchema t -> ParamSchema t -> Bool
(ParamSchema t -> ParamSchema t -> Bool)
-> (ParamSchema t -> ParamSchema t -> Bool) -> Eq (ParamSchema t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (t :: SwaggerKind *). ParamSchema t -> ParamSchema t -> Bool
/= :: ParamSchema t -> ParamSchema t -> Bool
$c/= :: forall (t :: SwaggerKind *). ParamSchema t -> ParamSchema t -> Bool
== :: ParamSchema t -> ParamSchema t -> Bool
$c== :: forall (t :: SwaggerKind *). ParamSchema t -> ParamSchema t -> Bool
Eq, Int -> ParamSchema t -> ShowS
[ParamSchema t] -> ShowS
ParamSchema t -> FilePath
(Int -> ParamSchema t -> ShowS)
-> (ParamSchema t -> FilePath)
-> ([ParamSchema t] -> ShowS)
-> Show (ParamSchema t)
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
forall (t :: SwaggerKind *). Int -> ParamSchema t -> ShowS
forall (t :: SwaggerKind *). [ParamSchema t] -> ShowS
forall (t :: SwaggerKind *). ParamSchema t -> FilePath
showList :: [ParamSchema t] -> ShowS
$cshowList :: forall (t :: SwaggerKind *). [ParamSchema t] -> ShowS
show :: ParamSchema t -> FilePath
$cshow :: forall (t :: SwaggerKind *). ParamSchema t -> FilePath
showsPrec :: Int -> ParamSchema t -> ShowS
$cshowsPrec :: forall (t :: SwaggerKind *). Int -> ParamSchema t -> ShowS
Show, (forall x. ParamSchema t -> Rep (ParamSchema t) x)
-> (forall x. Rep (ParamSchema t) x -> ParamSchema t)
-> Generic (ParamSchema t)
forall x. Rep (ParamSchema t) x -> ParamSchema t
forall x. ParamSchema t -> Rep (ParamSchema t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (t :: SwaggerKind *) x.
Rep (ParamSchema t) x -> ParamSchema t
forall (t :: SwaggerKind *) x.
ParamSchema t -> Rep (ParamSchema t) x
$cto :: forall (t :: SwaggerKind *) x.
Rep (ParamSchema t) x -> ParamSchema t
$cfrom :: forall (t :: SwaggerKind *) x.
ParamSchema t -> Rep (ParamSchema t) x
Generic, Typeable)

deriving instance (Typeable k, Data (Maybe (SwaggerType k)), Data (SwaggerItems k)) => Data (ParamSchema k)

data Xml = Xml
  { -- | 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.
    Xml -> Maybe Text
_xmlName :: Maybe Text

    -- | The URL of the namespace definition.
    -- Value SHOULD be in the form of a URL.
  , Xml -> Maybe Text
_xmlNamespace :: Maybe Text

    -- | The prefix to be used for the name.
  , Xml -> Maybe Text
_xmlPrefix :: Maybe Text

    -- | Declares whether the property definition translates to an attribute instead of an element.
    -- Default value is @False@.
  , Xml -> Maybe Bool
_xmlAttribute :: 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).
  , Xml -> Maybe Bool
_xmlWrapped :: Maybe Bool
  } deriving (Xml -> Xml -> Bool
(Xml -> Xml -> Bool) -> (Xml -> Xml -> Bool) -> Eq Xml
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Xml -> Xml -> Bool
$c/= :: Xml -> Xml -> Bool
== :: Xml -> Xml -> Bool
$c== :: Xml -> Xml -> Bool
Eq, Int -> Xml -> ShowS
[Xml] -> ShowS
Xml -> FilePath
(Int -> Xml -> ShowS)
-> (Xml -> FilePath) -> ([Xml] -> ShowS) -> Show Xml
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Xml] -> ShowS
$cshowList :: [Xml] -> ShowS
show :: Xml -> FilePath
$cshow :: Xml -> FilePath
showsPrec :: Int -> Xml -> ShowS
$cshowsPrec :: Int -> Xml -> ShowS
Show, (forall x. Xml -> Rep Xml x)
-> (forall x. Rep Xml x -> Xml) -> Generic Xml
forall x. Rep Xml x -> Xml
forall x. Xml -> Rep Xml x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Xml x -> Xml
$cfrom :: forall x. Xml -> Rep Xml x
Generic, Typeable Xml
DataType
Constr
Typeable Xml =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Xml -> c Xml)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Xml)
-> (Xml -> Constr)
-> (Xml -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Xml))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml))
-> ((forall b. Data b => b -> b) -> Xml -> Xml)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r)
-> (forall u. (forall d. Data d => d -> u) -> Xml -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Xml -> m Xml)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Xml -> m Xml)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Xml -> m Xml)
-> Data Xml
Xml -> DataType
Xml -> Constr
(forall b. Data b => b -> b) -> Xml -> Xml
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
forall u. (forall d. Data d => d -> u) -> Xml -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Xml)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml)
$cXml :: Constr
$tXml :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Xml -> m Xml
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
gmapMp :: (forall d. Data d => d -> m d) -> Xml -> m Xml
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
gmapM :: (forall d. Data d => d -> m d) -> Xml -> m Xml
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
gmapQi :: Int -> (forall d. Data d => d -> u) -> Xml -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
gmapQ :: (forall d. Data d => d -> u) -> Xml -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Xml -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
gmapT :: (forall b. Data b => b -> b) -> Xml -> Xml
$cgmapT :: (forall b. Data b => b -> b) -> Xml -> Xml
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Xml)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Xml)
dataTypeOf :: Xml -> DataType
$cdataTypeOf :: Xml -> DataType
toConstr :: Xml -> Constr
$ctoConstr :: Xml -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
$cp1Data :: Typeable Xml
Data, Typeable)

-- | 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.
data Responses = Responses
  { -- | The documentation of responses other than the ones declared for specific HTTP response codes.
    -- It can be used to cover undeclared responses.
   Responses -> Maybe (Referenced Response)
_responsesDefault :: Maybe (Referenced Response)

    -- | Any HTTP status code can be used as the property name (one property per HTTP status code).
    -- Describes the expected response for those HTTP status codes.
  , Responses -> InsOrdHashMap Int (Referenced Response)
_responsesResponses :: InsOrdHashMap HttpStatusCode (Referenced Response)
  } deriving (Responses -> Responses -> Bool
(Responses -> Responses -> Bool)
-> (Responses -> Responses -> Bool) -> Eq Responses
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Responses -> Responses -> Bool
$c/= :: Responses -> Responses -> Bool
== :: Responses -> Responses -> Bool
$c== :: Responses -> Responses -> Bool
Eq, Int -> Responses -> ShowS
[Responses] -> ShowS
Responses -> FilePath
(Int -> Responses -> ShowS)
-> (Responses -> FilePath)
-> ([Responses] -> ShowS)
-> Show Responses
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Responses] -> ShowS
$cshowList :: [Responses] -> ShowS
show :: Responses -> FilePath
$cshow :: Responses -> FilePath
showsPrec :: Int -> Responses -> ShowS
$cshowsPrec :: Int -> Responses -> ShowS
Show, (forall x. Responses -> Rep Responses x)
-> (forall x. Rep Responses x -> Responses) -> Generic Responses
forall x. Rep Responses x -> Responses
forall x. Responses -> Rep Responses x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Responses x -> Responses
$cfrom :: forall x. Responses -> Rep Responses x
Generic, Typeable Responses
DataType
Constr
Typeable Responses =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Responses -> c Responses)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Responses)
-> (Responses -> Constr)
-> (Responses -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Responses))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses))
-> ((forall b. Data b => b -> b) -> Responses -> Responses)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Responses -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Responses -> r)
-> (forall u. (forall d. Data d => d -> u) -> Responses -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Responses -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Responses -> m Responses)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Responses -> m Responses)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Responses -> m Responses)
-> Data Responses
Responses -> DataType
Responses -> Constr
(forall b. Data b => b -> b) -> Responses -> Responses
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
forall u. (forall d. Data d => d -> u) -> Responses -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Responses)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses)
$cResponses :: Constr
$tResponses :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Responses -> m Responses
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
gmapMp :: (forall d. Data d => d -> m d) -> Responses -> m Responses
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
gmapM :: (forall d. Data d => d -> m d) -> Responses -> m Responses
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
gmapQi :: Int -> (forall d. Data d => d -> u) -> Responses -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
gmapQ :: (forall d. Data d => d -> u) -> Responses -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Responses -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
gmapT :: (forall b. Data b => b -> b) -> Responses -> Responses
$cgmapT :: (forall b. Data b => b -> b) -> Responses -> Responses
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Responses)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Responses)
dataTypeOf :: Responses -> DataType
$cdataTypeOf :: Responses -> DataType
toConstr :: Responses -> Constr
$ctoConstr :: Responses -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
$cp1Data :: Typeable Responses
Data, Typeable)

type HttpStatusCode = Int

-- | Describes a single response from an API Operation.
data Response = Response
  { -- | A short description of the response.
    -- GFM syntax can be used for rich text representation.
    Response -> Text
_responseDescription :: Text

    -- | A definition of the response structure.
    -- It can be a primitive, an array or an object.
    -- If this field does not exist, it means no content is returned as part of the response.
    -- As an extension to the Schema Object, its root type value may also be "file".
    -- This SHOULD be accompanied by a relevant produces mime-type.
  , Response -> Maybe (Referenced Schema)
_responseSchema :: Maybe (Referenced Schema)

    -- | A list of headers that are sent with the response.
  , Response -> InsOrdHashMap Text Header
_responseHeaders :: InsOrdHashMap HeaderName Header

    -- | An example of the response message.
  , Response -> Maybe Example
_responseExamples :: Maybe Example
  } deriving (Response -> Response -> Bool
(Response -> Response -> Bool)
-> (Response -> Response -> Bool) -> Eq Response
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c== :: Response -> Response -> Bool
Eq, Int -> Response -> ShowS
[Response] -> ShowS
Response -> FilePath
(Int -> Response -> ShowS)
-> (Response -> FilePath) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Response] -> ShowS
$cshowList :: [Response] -> ShowS
show :: Response -> FilePath
$cshow :: Response -> FilePath
showsPrec :: Int -> Response -> ShowS
$cshowsPrec :: Int -> Response -> ShowS
Show, (forall x. Response -> Rep Response x)
-> (forall x. Rep Response x -> Response) -> Generic Response
forall x. Rep Response x -> Response
forall x. Response -> Rep Response x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Response x -> Response
$cfrom :: forall x. Response -> Rep Response x
Generic, Typeable Response
DataType
Constr
Typeable Response =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Response -> c Response)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Response)
-> (Response -> Constr)
-> (Response -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Response))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response))
-> ((forall b. Data b => b -> b) -> Response -> Response)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Response -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Response -> r)
-> (forall u. (forall d. Data d => d -> u) -> Response -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Response -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Response -> m Response)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Response -> m Response)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Response -> m Response)
-> Data Response
Response -> DataType
Response -> Constr
(forall b. Data b => b -> b) -> Response -> Response
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
forall u. (forall d. Data d => d -> u) -> Response -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Response -> m Response
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Response)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response)
$cResponse :: Constr
$tResponse :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Response -> m Response
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response
gmapMp :: (forall d. Data d => d -> m d) -> Response -> m Response
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response
gmapM :: (forall d. Data d => d -> m d) -> Response -> m Response
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Response -> m Response
gmapQi :: Int -> (forall d. Data d => d -> u) -> Response -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
gmapQ :: (forall d. Data d => d -> u) -> Response -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Response -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
gmapT :: (forall b. Data b => b -> b) -> Response -> Response
$cgmapT :: (forall b. Data b => b -> b) -> Response -> Response
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Response)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Response)
dataTypeOf :: Response -> DataType
$cdataTypeOf :: Response -> DataType
toConstr :: Response -> Constr
$ctoConstr :: Response -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
$cp1Data :: Typeable Response
Data, Typeable)

instance IsString Response where
  fromString :: FilePath -> Response
fromString s :: FilePath
s = Text
-> Maybe (Referenced Schema)
-> InsOrdHashMap Text Header
-> Maybe Example
-> Response
Response (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe (Referenced Schema)
forall a. Maybe a
Nothing InsOrdHashMap Text Header
forall a. Monoid a => a
mempty Maybe Example
forall a. Maybe a
Nothing

type HeaderName = Text

data Header = Header
  { -- | A short description of the header.
    Header -> Maybe Text
_headerDescription :: Maybe Text

  , Header -> ParamSchema ('SwaggerKindNormal Header)
_headerParamSchema :: ParamSchema ('SwaggerKindNormal Header)
  } deriving (Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c== :: Header -> Header -> Bool
Eq, Int -> Header -> ShowS
[Header] -> ShowS
Header -> FilePath
(Int -> Header -> ShowS)
-> (Header -> FilePath) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> FilePath
$cshow :: Header -> FilePath
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show, (forall x. Header -> Rep Header x)
-> (forall x. Rep Header x -> Header) -> Generic Header
forall x. Rep Header x -> Header
forall x. Header -> Rep Header x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Header x -> Header
$cfrom :: forall x. Header -> Rep Header x
Generic, Typeable Header
DataType
Constr
Typeable Header =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Header -> c Header)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Header)
-> (Header -> Constr)
-> (Header -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Header))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header))
-> ((forall b. Data b => b -> b) -> Header -> Header)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall u. (forall d. Data d => d -> u) -> Header -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Header -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Header -> m Header)
-> Data Header
Header -> DataType
Header -> Constr
(forall b. Data b => b -> b) -> Header -> Header
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
forall u. (forall d. Data d => d -> u) -> Header -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
$cHeader :: Constr
$tHeader :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Header -> m Header
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapMp :: (forall d. Data d => d -> m d) -> Header -> m Header
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapM :: (forall d. Data d => d -> m d) -> Header -> m Header
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapQi :: Int -> (forall d. Data d => d -> u) -> Header -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
gmapQ :: (forall d. Data d => d -> u) -> Header -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
gmapT :: (forall b. Data b => b -> b) -> Header -> Header
$cgmapT :: (forall b. Data b => b -> b) -> Header -> Header
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Header)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
dataTypeOf :: Header -> DataType
$cdataTypeOf :: Header -> DataType
toConstr :: Header -> Constr
$ctoConstr :: Header -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
$cp1Data :: Typeable Header
Data, Typeable)

data Example = Example { Example -> Map MediaType Value
getExample :: Map MediaType Value }
  deriving (Example -> Example -> Bool
(Example -> Example -> Bool)
-> (Example -> Example -> Bool) -> Eq Example
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Example -> Example -> Bool
$c/= :: Example -> Example -> Bool
== :: Example -> Example -> Bool
$c== :: Example -> Example -> Bool
Eq, Int -> Example -> ShowS
[Example] -> ShowS
Example -> FilePath
(Int -> Example -> ShowS)
-> (Example -> FilePath) -> ([Example] -> ShowS) -> Show Example
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Example] -> ShowS
$cshowList :: [Example] -> ShowS
show :: Example -> FilePath
$cshow :: Example -> FilePath
showsPrec :: Int -> Example -> ShowS
$cshowsPrec :: Int -> Example -> ShowS
Show, (forall x. Example -> Rep Example x)
-> (forall x. Rep Example x -> Example) -> Generic Example
forall x. Rep Example x -> Example
forall x. Example -> Rep Example x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Example x -> Example
$cfrom :: forall x. Example -> Rep Example x
Generic, Typeable)

exampleConstr :: Constr
exampleConstr :: Constr
exampleConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
exampleDataType "Example" ["getExample"] Fixity
Prefix

exampleDataType :: DataType
exampleDataType :: DataType
exampleDataType = FilePath -> [Constr] -> DataType
mkDataType "Data.Swagger.Example" [Constr
exampleConstr]

instance Data Example where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
gunfold k :: forall b r. Data b => c (b -> r) -> c r
k z :: forall r. r -> c r
z c :: Constr
c = case Constr -> Int
constrIndex Constr
c of
    1 -> c (Map FilePath Value -> Example) -> c Example
forall b r. Data b => c (b -> r) -> c r
k ((Map FilePath Value -> Example)
-> c (Map FilePath Value -> Example)
forall r. r -> c r
z (\m :: Map FilePath Value
m -> Map MediaType Value -> Example
Example ((FilePath -> MediaType)
-> Map FilePath Value -> Map MediaType Value
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString Map FilePath Value
m)))
    _ -> FilePath -> c Example
forall a. HasCallStack => FilePath -> a
error (FilePath -> c Example) -> FilePath -> c Example
forall a b. (a -> b) -> a -> b
$ "Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ " is not of type Example."
  toConstr :: Example -> Constr
toConstr (Example _) = Constr
exampleConstr
  dataTypeOf :: Example -> DataType
dataTypeOf _ = DataType
exampleDataType

-- | The location of the API key.
data ApiKeyLocation
  = ApiKeyQuery
  | ApiKeyHeader
  deriving (ApiKeyLocation -> ApiKeyLocation -> Bool
(ApiKeyLocation -> ApiKeyLocation -> Bool)
-> (ApiKeyLocation -> ApiKeyLocation -> Bool) -> Eq ApiKeyLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiKeyLocation -> ApiKeyLocation -> Bool
$c/= :: ApiKeyLocation -> ApiKeyLocation -> Bool
== :: ApiKeyLocation -> ApiKeyLocation -> Bool
$c== :: ApiKeyLocation -> ApiKeyLocation -> Bool
Eq, Int -> ApiKeyLocation -> ShowS
[ApiKeyLocation] -> ShowS
ApiKeyLocation -> FilePath
(Int -> ApiKeyLocation -> ShowS)
-> (ApiKeyLocation -> FilePath)
-> ([ApiKeyLocation] -> ShowS)
-> Show ApiKeyLocation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ApiKeyLocation] -> ShowS
$cshowList :: [ApiKeyLocation] -> ShowS
show :: ApiKeyLocation -> FilePath
$cshow :: ApiKeyLocation -> FilePath
showsPrec :: Int -> ApiKeyLocation -> ShowS
$cshowsPrec :: Int -> ApiKeyLocation -> ShowS
Show, (forall x. ApiKeyLocation -> Rep ApiKeyLocation x)
-> (forall x. Rep ApiKeyLocation x -> ApiKeyLocation)
-> Generic ApiKeyLocation
forall x. Rep ApiKeyLocation x -> ApiKeyLocation
forall x. ApiKeyLocation -> Rep ApiKeyLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ApiKeyLocation x -> ApiKeyLocation
$cfrom :: forall x. ApiKeyLocation -> Rep ApiKeyLocation x
Generic, Typeable ApiKeyLocation
DataType
Constr
Typeable ApiKeyLocation =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ApiKeyLocation)
-> (ApiKeyLocation -> Constr)
-> (ApiKeyLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ApiKeyLocation))
-> ((forall b. Data b => b -> b)
    -> ApiKeyLocation -> ApiKeyLocation)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ApiKeyLocation -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ApiKeyLocation -> m ApiKeyLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ApiKeyLocation -> m ApiKeyLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ApiKeyLocation -> m ApiKeyLocation)
-> Data ApiKeyLocation
ApiKeyLocation -> DataType
ApiKeyLocation -> Constr
(forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation)
$cApiKeyHeader :: Constr
$cApiKeyQuery :: Constr
$tApiKeyLocation :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
gmapMp :: (forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
gmapM :: (forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
gmapQi :: Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
gmapQ :: (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
gmapT :: (forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation
$cgmapT :: (forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation)
dataTypeOf :: ApiKeyLocation -> DataType
$cdataTypeOf :: ApiKeyLocation -> DataType
toConstr :: ApiKeyLocation -> Constr
$ctoConstr :: ApiKeyLocation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
$cp1Data :: Typeable ApiKeyLocation
Data, Typeable)

data ApiKeyParams = ApiKeyParams
  { -- | The name of the header or query parameter to be used.
    ApiKeyParams -> Text
_apiKeyName :: Text

    -- | The location of the API key.
  , ApiKeyParams -> ApiKeyLocation
_apiKeyIn :: ApiKeyLocation
  } deriving (ApiKeyParams -> ApiKeyParams -> Bool
(ApiKeyParams -> ApiKeyParams -> Bool)
-> (ApiKeyParams -> ApiKeyParams -> Bool) -> Eq ApiKeyParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiKeyParams -> ApiKeyParams -> Bool
$c/= :: ApiKeyParams -> ApiKeyParams -> Bool
== :: ApiKeyParams -> ApiKeyParams -> Bool
$c== :: ApiKeyParams -> ApiKeyParams -> Bool
Eq, Int -> ApiKeyParams -> ShowS
[ApiKeyParams] -> ShowS
ApiKeyParams -> FilePath
(Int -> ApiKeyParams -> ShowS)
-> (ApiKeyParams -> FilePath)
-> ([ApiKeyParams] -> ShowS)
-> Show ApiKeyParams
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ApiKeyParams] -> ShowS
$cshowList :: [ApiKeyParams] -> ShowS
show :: ApiKeyParams -> FilePath
$cshow :: ApiKeyParams -> FilePath
showsPrec :: Int -> ApiKeyParams -> ShowS
$cshowsPrec :: Int -> ApiKeyParams -> ShowS
Show, (forall x. ApiKeyParams -> Rep ApiKeyParams x)
-> (forall x. Rep ApiKeyParams x -> ApiKeyParams)
-> Generic ApiKeyParams
forall x. Rep ApiKeyParams x -> ApiKeyParams
forall x. ApiKeyParams -> Rep ApiKeyParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ApiKeyParams x -> ApiKeyParams
$cfrom :: forall x. ApiKeyParams -> Rep ApiKeyParams x
Generic, Typeable ApiKeyParams
DataType
Constr
Typeable ApiKeyParams =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ApiKeyParams)
-> (ApiKeyParams -> Constr)
-> (ApiKeyParams -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ApiKeyParams))
-> ((forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r)
-> (forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> Data ApiKeyParams
ApiKeyParams -> DataType
ApiKeyParams -> Constr
(forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams)
$cApiKeyParams :: Constr
$tApiKeyParams :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
gmapMp :: (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
gmapM :: (forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
gmapQi :: Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
gmapQ :: (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
gmapT :: (forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams
$cgmapT :: (forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams)
dataTypeOf :: ApiKeyParams -> DataType
$cdataTypeOf :: ApiKeyParams -> DataType
toConstr :: ApiKeyParams -> Constr
$ctoConstr :: ApiKeyParams -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
$cp1Data :: Typeable ApiKeyParams
Data, Typeable)

-- | The authorization URL to be used for OAuth2 flow. This SHOULD be in the form of a URL.
type AuthorizationURL = Text

-- | The token URL to be used for OAuth2 flow. This SHOULD be in the form of a URL.
type TokenURL = Text

data OAuth2Flow
  = OAuth2Implicit AuthorizationURL
  | OAuth2Password TokenURL
  | OAuth2Application TokenURL
  | OAuth2AccessCode AuthorizationURL TokenURL
  deriving (OAuth2Flow -> OAuth2Flow -> Bool
(OAuth2Flow -> OAuth2Flow -> Bool)
-> (OAuth2Flow -> OAuth2Flow -> Bool) -> Eq OAuth2Flow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OAuth2Flow -> OAuth2Flow -> Bool
$c/= :: OAuth2Flow -> OAuth2Flow -> Bool
== :: OAuth2Flow -> OAuth2Flow -> Bool
$c== :: OAuth2Flow -> OAuth2Flow -> Bool
Eq, Int -> OAuth2Flow -> ShowS
[OAuth2Flow] -> ShowS
OAuth2Flow -> FilePath
(Int -> OAuth2Flow -> ShowS)
-> (OAuth2Flow -> FilePath)
-> ([OAuth2Flow] -> ShowS)
-> Show OAuth2Flow
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OAuth2Flow] -> ShowS
$cshowList :: [OAuth2Flow] -> ShowS
show :: OAuth2Flow -> FilePath
$cshow :: OAuth2Flow -> FilePath
showsPrec :: Int -> OAuth2Flow -> ShowS
$cshowsPrec :: Int -> OAuth2Flow -> ShowS
Show, (forall x. OAuth2Flow -> Rep OAuth2Flow x)
-> (forall x. Rep OAuth2Flow x -> OAuth2Flow) -> Generic OAuth2Flow
forall x. Rep OAuth2Flow x -> OAuth2Flow
forall x. OAuth2Flow -> Rep OAuth2Flow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OAuth2Flow x -> OAuth2Flow
$cfrom :: forall x. OAuth2Flow -> Rep OAuth2Flow x
Generic, Typeable OAuth2Flow
DataType
Constr
Typeable OAuth2Flow =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OAuth2Flow)
-> (OAuth2Flow -> Constr)
-> (OAuth2Flow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OAuth2Flow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OAuth2Flow))
-> ((forall b. Data b => b -> b) -> OAuth2Flow -> OAuth2Flow)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r)
-> (forall u. (forall d. Data d => d -> u) -> OAuth2Flow -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OAuth2Flow -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow)
-> Data OAuth2Flow
OAuth2Flow -> DataType
OAuth2Flow -> Constr
(forall b. Data b => b -> b) -> OAuth2Flow -> OAuth2Flow
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flow
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flow -> u
forall u. (forall d. Data d => d -> u) -> OAuth2Flow -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flow
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Flow)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth2Flow)
$cOAuth2AccessCode :: Constr
$cOAuth2Application :: Constr
$cOAuth2Password :: Constr
$cOAuth2Implicit :: Constr
$tOAuth2Flow :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
gmapMp :: (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
gmapM :: (forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flow -> m OAuth2Flow
gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth2Flow -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flow -> u
gmapQ :: (forall d. Data d => d -> u) -> OAuth2Flow -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Flow -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow -> r
gmapT :: (forall b. Data b => b -> b) -> OAuth2Flow -> OAuth2Flow
$cgmapT :: (forall b. Data b => b -> b) -> OAuth2Flow -> OAuth2Flow
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth2Flow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth2Flow)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OAuth2Flow)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Flow)
dataTypeOf :: OAuth2Flow -> DataType
$cdataTypeOf :: OAuth2Flow -> DataType
toConstr :: OAuth2Flow -> Constr
$ctoConstr :: OAuth2Flow -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flow
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow -> c OAuth2Flow
$cp1Data :: Typeable OAuth2Flow
Data, Typeable)

data OAuth2Params = OAuth2Params
  { -- | The flow used by the OAuth2 security scheme.
    OAuth2Params -> OAuth2Flow
_oauth2Flow :: OAuth2Flow

    -- | The available scopes for the OAuth2 security scheme.
  , OAuth2Params -> InsOrdHashMap Text Text
_oauth2Scopes :: InsOrdHashMap Text Text
  } deriving (OAuth2Params -> OAuth2Params -> Bool
(OAuth2Params -> OAuth2Params -> Bool)
-> (OAuth2Params -> OAuth2Params -> Bool) -> Eq OAuth2Params
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OAuth2Params -> OAuth2Params -> Bool
$c/= :: OAuth2Params -> OAuth2Params -> Bool
== :: OAuth2Params -> OAuth2Params -> Bool
$c== :: OAuth2Params -> OAuth2Params -> Bool
Eq, Int -> OAuth2Params -> ShowS
[OAuth2Params] -> ShowS
OAuth2Params -> FilePath
(Int -> OAuth2Params -> ShowS)
-> (OAuth2Params -> FilePath)
-> ([OAuth2Params] -> ShowS)
-> Show OAuth2Params
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OAuth2Params] -> ShowS
$cshowList :: [OAuth2Params] -> ShowS
show :: OAuth2Params -> FilePath
$cshow :: OAuth2Params -> FilePath
showsPrec :: Int -> OAuth2Params -> ShowS
$cshowsPrec :: Int -> OAuth2Params -> ShowS
Show, (forall x. OAuth2Params -> Rep OAuth2Params x)
-> (forall x. Rep OAuth2Params x -> OAuth2Params)
-> Generic OAuth2Params
forall x. Rep OAuth2Params x -> OAuth2Params
forall x. OAuth2Params -> Rep OAuth2Params x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OAuth2Params x -> OAuth2Params
$cfrom :: forall x. OAuth2Params -> Rep OAuth2Params x
Generic, Typeable OAuth2Params
DataType
Constr
Typeable OAuth2Params =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OAuth2Params)
-> (OAuth2Params -> Constr)
-> (OAuth2Params -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OAuth2Params))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OAuth2Params))
-> ((forall b. Data b => b -> b) -> OAuth2Params -> OAuth2Params)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r)
-> (forall u. (forall d. Data d => d -> u) -> OAuth2Params -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OAuth2Params -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params)
-> Data OAuth2Params
OAuth2Params -> DataType
OAuth2Params -> Constr
(forall b. Data b => b -> b) -> OAuth2Params -> OAuth2Params
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Params
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Params -> u
forall u. (forall d. Data d => d -> u) -> OAuth2Params -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Params
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Params)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Params)
$cOAuth2Params :: Constr
$tOAuth2Params :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
gmapMp :: (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
gmapM :: (forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Params -> m OAuth2Params
gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth2Params -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Params -> u
gmapQ :: (forall d. Data d => d -> u) -> OAuth2Params -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Params -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Params -> r
gmapT :: (forall b. Data b => b -> b) -> OAuth2Params -> OAuth2Params
$cgmapT :: (forall b. Data b => b -> b) -> OAuth2Params -> OAuth2Params
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Params)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Params)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OAuth2Params)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Params)
dataTypeOf :: OAuth2Params -> DataType
$cdataTypeOf :: OAuth2Params -> DataType
toConstr :: OAuth2Params -> Constr
$ctoConstr :: OAuth2Params -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Params
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Params
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Params -> c OAuth2Params
$cp1Data :: Typeable OAuth2Params
Data, Typeable)

data SecuritySchemeType
  = SecuritySchemeBasic
  | SecuritySchemeApiKey ApiKeyParams
  | SecuritySchemeOAuth2 OAuth2Params
  deriving (SecuritySchemeType -> SecuritySchemeType -> Bool
(SecuritySchemeType -> SecuritySchemeType -> Bool)
-> (SecuritySchemeType -> SecuritySchemeType -> Bool)
-> Eq SecuritySchemeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecuritySchemeType -> SecuritySchemeType -> Bool
$c/= :: SecuritySchemeType -> SecuritySchemeType -> Bool
== :: SecuritySchemeType -> SecuritySchemeType -> Bool
$c== :: SecuritySchemeType -> SecuritySchemeType -> Bool
Eq, Int -> SecuritySchemeType -> ShowS
[SecuritySchemeType] -> ShowS
SecuritySchemeType -> FilePath
(Int -> SecuritySchemeType -> ShowS)
-> (SecuritySchemeType -> FilePath)
-> ([SecuritySchemeType] -> ShowS)
-> Show SecuritySchemeType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SecuritySchemeType] -> ShowS
$cshowList :: [SecuritySchemeType] -> ShowS
show :: SecuritySchemeType -> FilePath
$cshow :: SecuritySchemeType -> FilePath
showsPrec :: Int -> SecuritySchemeType -> ShowS
$cshowsPrec :: Int -> SecuritySchemeType -> ShowS
Show, (forall x. SecuritySchemeType -> Rep SecuritySchemeType x)
-> (forall x. Rep SecuritySchemeType x -> SecuritySchemeType)
-> Generic SecuritySchemeType
forall x. Rep SecuritySchemeType x -> SecuritySchemeType
forall x. SecuritySchemeType -> Rep SecuritySchemeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecuritySchemeType x -> SecuritySchemeType
$cfrom :: forall x. SecuritySchemeType -> Rep SecuritySchemeType x
Generic, Typeable SecuritySchemeType
DataType
Constr
Typeable SecuritySchemeType =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> SecuritySchemeType
 -> c SecuritySchemeType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SecuritySchemeType)
-> (SecuritySchemeType -> Constr)
-> (SecuritySchemeType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SecuritySchemeType))
-> ((forall b. Data b => b -> b)
    -> SecuritySchemeType -> SecuritySchemeType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SecuritySchemeType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SecuritySchemeType -> m SecuritySchemeType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecuritySchemeType -> m SecuritySchemeType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecuritySchemeType -> m SecuritySchemeType)
-> Data SecuritySchemeType
SecuritySchemeType -> DataType
SecuritySchemeType -> Constr
(forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType)
$cSecuritySchemeOAuth2 :: Constr
$cSecuritySchemeApiKey :: Constr
$cSecuritySchemeBasic :: Constr
$tSecuritySchemeType :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
gmapMp :: (forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
gmapM :: (forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
gmapQi :: Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
gmapQ :: (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
gmapT :: (forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType
$cgmapT :: (forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType)
dataTypeOf :: SecuritySchemeType -> DataType
$cdataTypeOf :: SecuritySchemeType -> DataType
toConstr :: SecuritySchemeType -> Constr
$ctoConstr :: SecuritySchemeType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
$cp1Data :: Typeable SecuritySchemeType
Data, Typeable)

data SecurityScheme = SecurityScheme
  { -- | The type of the security scheme.
    SecurityScheme -> SecuritySchemeType
_securitySchemeType :: SecuritySchemeType

    -- | A short description for security scheme.
  , SecurityScheme -> Maybe Text
_securitySchemeDescription :: Maybe Text
  } deriving (SecurityScheme -> SecurityScheme -> Bool
(SecurityScheme -> SecurityScheme -> Bool)
-> (SecurityScheme -> SecurityScheme -> Bool) -> Eq SecurityScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecurityScheme -> SecurityScheme -> Bool
$c/= :: SecurityScheme -> SecurityScheme -> Bool
== :: SecurityScheme -> SecurityScheme -> Bool
$c== :: SecurityScheme -> SecurityScheme -> Bool
Eq, Int -> SecurityScheme -> ShowS
[SecurityScheme] -> ShowS
SecurityScheme -> FilePath
(Int -> SecurityScheme -> ShowS)
-> (SecurityScheme -> FilePath)
-> ([SecurityScheme] -> ShowS)
-> Show SecurityScheme
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SecurityScheme] -> ShowS
$cshowList :: [SecurityScheme] -> ShowS
show :: SecurityScheme -> FilePath
$cshow :: SecurityScheme -> FilePath
showsPrec :: Int -> SecurityScheme -> ShowS
$cshowsPrec :: Int -> SecurityScheme -> ShowS
Show, (forall x. SecurityScheme -> Rep SecurityScheme x)
-> (forall x. Rep SecurityScheme x -> SecurityScheme)
-> Generic SecurityScheme
forall x. Rep SecurityScheme x -> SecurityScheme
forall x. SecurityScheme -> Rep SecurityScheme x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecurityScheme x -> SecurityScheme
$cfrom :: forall x. SecurityScheme -> Rep SecurityScheme x
Generic, Typeable SecurityScheme
DataType
Constr
Typeable SecurityScheme =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SecurityScheme)
-> (SecurityScheme -> Constr)
-> (SecurityScheme -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SecurityScheme))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SecurityScheme))
-> ((forall b. Data b => b -> b)
    -> SecurityScheme -> SecurityScheme)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SecurityScheme -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SecurityScheme -> m SecurityScheme)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityScheme -> m SecurityScheme)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityScheme -> m SecurityScheme)
-> Data SecurityScheme
SecurityScheme -> DataType
SecurityScheme -> Constr
(forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityScheme)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme)
$cSecurityScheme :: Constr
$tSecurityScheme :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
gmapMp :: (forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
gmapM :: (forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
gmapQ :: (forall d. Data d => d -> u) -> SecurityScheme -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
gmapT :: (forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme
$cgmapT :: (forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SecurityScheme)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityScheme)
dataTypeOf :: SecurityScheme -> DataType
$cdataTypeOf :: SecurityScheme -> DataType
toConstr :: SecurityScheme -> Constr
$ctoConstr :: SecurityScheme -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
$cp1Data :: Typeable SecurityScheme
Data, Typeable)


-- | merge scopes of two OAuth2 security schemes when their flows are identical.
-- In other case returns first security scheme
mergeSecurityScheme :: SecurityScheme -> SecurityScheme -> SecurityScheme
mergeSecurityScheme :: SecurityScheme -> SecurityScheme -> SecurityScheme
mergeSecurityScheme s1 :: SecurityScheme
s1@(SecurityScheme (SecuritySchemeOAuth2 (OAuth2Params flow1 :: OAuth2Flow
flow1 scopes1 :: InsOrdHashMap Text Text
scopes1)) desc :: Maybe Text
desc)
                    s2 :: SecurityScheme
s2@(SecurityScheme (SecuritySchemeOAuth2 (OAuth2Params flow2 :: OAuth2Flow
flow2 scopes2 :: InsOrdHashMap Text Text
scopes2)) _)
  = if OAuth2Flow
flow1 OAuth2Flow -> OAuth2Flow -> Bool
forall a. Eq a => a -> a -> Bool
== OAuth2Flow
flow2 then
      SecuritySchemeType -> Maybe Text -> SecurityScheme
SecurityScheme (OAuth2Params -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Flow -> InsOrdHashMap Text Text -> OAuth2Params
OAuth2Params OAuth2Flow
flow1 (InsOrdHashMap Text Text
scopes1 InsOrdHashMap Text Text
-> InsOrdHashMap Text Text -> InsOrdHashMap Text Text
forall a. Semigroup a => a -> a -> a
<> InsOrdHashMap Text Text
scopes2))) Maybe Text
desc
    else
      SecurityScheme
s1
mergeSecurityScheme s1 :: SecurityScheme
s1 _ = SecurityScheme
s1

newtype SecurityDefinitions
  = SecurityDefinitions (Definitions SecurityScheme)
  deriving (SecurityDefinitions -> SecurityDefinitions -> Bool
(SecurityDefinitions -> SecurityDefinitions -> Bool)
-> (SecurityDefinitions -> SecurityDefinitions -> Bool)
-> Eq SecurityDefinitions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecurityDefinitions -> SecurityDefinitions -> Bool
$c/= :: SecurityDefinitions -> SecurityDefinitions -> Bool
== :: SecurityDefinitions -> SecurityDefinitions -> Bool
$c== :: SecurityDefinitions -> SecurityDefinitions -> Bool
Eq, Int -> SecurityDefinitions -> ShowS
[SecurityDefinitions] -> ShowS
SecurityDefinitions -> FilePath
(Int -> SecurityDefinitions -> ShowS)
-> (SecurityDefinitions -> FilePath)
-> ([SecurityDefinitions] -> ShowS)
-> Show SecurityDefinitions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SecurityDefinitions] -> ShowS
$cshowList :: [SecurityDefinitions] -> ShowS
show :: SecurityDefinitions -> FilePath
$cshow :: SecurityDefinitions -> FilePath
showsPrec :: Int -> SecurityDefinitions -> ShowS
$cshowsPrec :: Int -> SecurityDefinitions -> ShowS
Show, (forall x. SecurityDefinitions -> Rep SecurityDefinitions x)
-> (forall x. Rep SecurityDefinitions x -> SecurityDefinitions)
-> Generic SecurityDefinitions
forall x. Rep SecurityDefinitions x -> SecurityDefinitions
forall x. SecurityDefinitions -> Rep SecurityDefinitions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecurityDefinitions x -> SecurityDefinitions
$cfrom :: forall x. SecurityDefinitions -> Rep SecurityDefinitions x
Generic, Typeable SecurityDefinitions
DataType
Constr
Typeable SecurityDefinitions =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> SecurityDefinitions
 -> c SecurityDefinitions)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SecurityDefinitions)
-> (SecurityDefinitions -> Constr)
-> (SecurityDefinitions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SecurityDefinitions))
-> ((forall b. Data b => b -> b)
    -> SecurityDefinitions -> SecurityDefinitions)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SecurityDefinitions -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SecurityDefinitions -> m SecurityDefinitions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityDefinitions -> m SecurityDefinitions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityDefinitions -> m SecurityDefinitions)
-> Data SecurityDefinitions
SecurityDefinitions -> DataType
SecurityDefinitions -> Constr
(forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions)
$cSecurityDefinitions :: Constr
$tSecurityDefinitions :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
gmapMp :: (forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
gmapM :: (forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
gmapQ :: (forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
gmapT :: (forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions
$cgmapT :: (forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions)
dataTypeOf :: SecurityDefinitions -> DataType
$cdataTypeOf :: SecurityDefinitions -> DataType
toConstr :: SecurityDefinitions -> Constr
$ctoConstr :: SecurityDefinitions -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
$cp1Data :: Typeable SecurityDefinitions
Data, Typeable)

-- | 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).
newtype SecurityRequirement = SecurityRequirement
  { SecurityRequirement -> InsOrdHashMap Text [Text]
getSecurityRequirement :: InsOrdHashMap Text [Text]
  } deriving (SecurityRequirement -> SecurityRequirement -> Bool
(SecurityRequirement -> SecurityRequirement -> Bool)
-> (SecurityRequirement -> SecurityRequirement -> Bool)
-> Eq SecurityRequirement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecurityRequirement -> SecurityRequirement -> Bool
$c/= :: SecurityRequirement -> SecurityRequirement -> Bool
== :: SecurityRequirement -> SecurityRequirement -> Bool
$c== :: SecurityRequirement -> SecurityRequirement -> Bool
Eq, ReadPrec [SecurityRequirement]
ReadPrec SecurityRequirement
Int -> ReadS SecurityRequirement
ReadS [SecurityRequirement]
(Int -> ReadS SecurityRequirement)
-> ReadS [SecurityRequirement]
-> ReadPrec SecurityRequirement
-> ReadPrec [SecurityRequirement]
-> Read SecurityRequirement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SecurityRequirement]
$creadListPrec :: ReadPrec [SecurityRequirement]
readPrec :: ReadPrec SecurityRequirement
$creadPrec :: ReadPrec SecurityRequirement
readList :: ReadS [SecurityRequirement]
$creadList :: ReadS [SecurityRequirement]
readsPrec :: Int -> ReadS SecurityRequirement
$creadsPrec :: Int -> ReadS SecurityRequirement
Read, Int -> SecurityRequirement -> ShowS
[SecurityRequirement] -> ShowS
SecurityRequirement -> FilePath
(Int -> SecurityRequirement -> ShowS)
-> (SecurityRequirement -> FilePath)
-> ([SecurityRequirement] -> ShowS)
-> Show SecurityRequirement
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SecurityRequirement] -> ShowS
$cshowList :: [SecurityRequirement] -> ShowS
show :: SecurityRequirement -> FilePath
$cshow :: SecurityRequirement -> FilePath
showsPrec :: Int -> SecurityRequirement -> ShowS
$cshowsPrec :: Int -> SecurityRequirement -> ShowS
Show, b -> SecurityRequirement -> SecurityRequirement
NonEmpty SecurityRequirement -> SecurityRequirement
SecurityRequirement -> SecurityRequirement -> SecurityRequirement
(SecurityRequirement -> SecurityRequirement -> SecurityRequirement)
-> (NonEmpty SecurityRequirement -> SecurityRequirement)
-> (forall b.
    Integral b =>
    b -> SecurityRequirement -> SecurityRequirement)
-> Semigroup SecurityRequirement
forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> SecurityRequirement -> SecurityRequirement
$cstimes :: forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement
sconcat :: NonEmpty SecurityRequirement -> SecurityRequirement
$csconcat :: NonEmpty SecurityRequirement -> SecurityRequirement
<> :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
$c<> :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
Semigroup, Semigroup SecurityRequirement
SecurityRequirement
Semigroup SecurityRequirement =>
SecurityRequirement
-> (SecurityRequirement
    -> SecurityRequirement -> SecurityRequirement)
-> ([SecurityRequirement] -> SecurityRequirement)
-> Monoid SecurityRequirement
[SecurityRequirement] -> SecurityRequirement
SecurityRequirement -> SecurityRequirement -> SecurityRequirement
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [SecurityRequirement] -> SecurityRequirement
$cmconcat :: [SecurityRequirement] -> SecurityRequirement
mappend :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
$cmappend :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
mempty :: SecurityRequirement
$cmempty :: SecurityRequirement
$cp1Monoid :: Semigroup SecurityRequirement
Monoid, [SecurityRequirement] -> Encoding
[SecurityRequirement] -> Value
SecurityRequirement -> Encoding
SecurityRequirement -> Value
(SecurityRequirement -> Value)
-> (SecurityRequirement -> Encoding)
-> ([SecurityRequirement] -> Value)
-> ([SecurityRequirement] -> Encoding)
-> ToJSON SecurityRequirement
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SecurityRequirement] -> Encoding
$ctoEncodingList :: [SecurityRequirement] -> Encoding
toJSONList :: [SecurityRequirement] -> Value
$ctoJSONList :: [SecurityRequirement] -> Value
toEncoding :: SecurityRequirement -> Encoding
$ctoEncoding :: SecurityRequirement -> Encoding
toJSON :: SecurityRequirement -> Value
$ctoJSON :: SecurityRequirement -> Value
ToJSON, Value -> Parser [SecurityRequirement]
Value -> Parser SecurityRequirement
(Value -> Parser SecurityRequirement)
-> (Value -> Parser [SecurityRequirement])
-> FromJSON SecurityRequirement
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SecurityRequirement]
$cparseJSONList :: Value -> Parser [SecurityRequirement]
parseJSON :: Value -> Parser SecurityRequirement
$cparseJSON :: Value -> Parser SecurityRequirement
FromJSON, Typeable SecurityRequirement
DataType
Constr
Typeable SecurityRequirement =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> SecurityRequirement
 -> c SecurityRequirement)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SecurityRequirement)
-> (SecurityRequirement -> Constr)
-> (SecurityRequirement -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SecurityRequirement))
-> ((forall b. Data b => b -> b)
    -> SecurityRequirement -> SecurityRequirement)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SecurityRequirement -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SecurityRequirement -> m SecurityRequirement)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityRequirement -> m SecurityRequirement)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SecurityRequirement -> m SecurityRequirement)
-> Data SecurityRequirement
SecurityRequirement -> DataType
SecurityRequirement -> Constr
(forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement)
$cSecurityRequirement :: Constr
$tSecurityRequirement :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
gmapMp :: (forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
gmapM :: (forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
gmapQ :: (forall d. Data d => d -> u) -> SecurityRequirement -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
gmapT :: (forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement
$cgmapT :: (forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement)
dataTypeOf :: SecurityRequirement -> DataType
$cdataTypeOf :: SecurityRequirement -> DataType
toConstr :: SecurityRequirement -> Constr
$ctoConstr :: SecurityRequirement -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
$cp1Data :: Typeable SecurityRequirement
Data, Typeable)

-- | Tag name.
type TagName = Text

-- | 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.
data Tag = Tag
  { -- | The name of the tag.
    Tag -> Text
_tagName :: TagName

    -- | A short description for the tag.
    -- GFM syntax can be used for rich text representation.
  , Tag -> Maybe Text
_tagDescription :: Maybe Text

    -- | Additional external documentation for this tag.
  , Tag -> Maybe ExternalDocs
_tagExternalDocs :: Maybe ExternalDocs
  } deriving (Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Eq, Eq Tag
Eq Tag =>
(Tag -> Tag -> Ordering)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Tag)
-> (Tag -> Tag -> Tag)
-> Ord Tag
Tag -> Tag -> Bool
Tag -> Tag -> Ordering
Tag -> Tag -> Tag
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmax :: Tag -> Tag -> Tag
>= :: Tag -> Tag -> Bool
$c>= :: Tag -> Tag -> Bool
> :: Tag -> Tag -> Bool
$c> :: Tag -> Tag -> Bool
<= :: Tag -> Tag -> Bool
$c<= :: Tag -> Tag -> Bool
< :: Tag -> Tag -> Bool
$c< :: Tag -> Tag -> Bool
compare :: Tag -> Tag -> Ordering
$ccompare :: Tag -> Tag -> Ordering
$cp1Ord :: Eq Tag
Ord, Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> FilePath
(Int -> Tag -> ShowS)
-> (Tag -> FilePath) -> ([Tag] -> ShowS) -> Show Tag
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> FilePath
$cshow :: Tag -> FilePath
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show, (forall x. Tag -> Rep Tag x)
-> (forall x. Rep Tag x -> Tag) -> Generic Tag
forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
Generic, Typeable Tag
DataType
Constr
Typeable Tag =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Tag -> c Tag)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Tag)
-> (Tag -> Constr)
-> (Tag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Tag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag))
-> ((forall b. Data b => b -> b) -> Tag -> Tag)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall u. (forall d. Data d => d -> u) -> Tag -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> Data Tag
Tag -> DataType
Tag -> Constr
(forall b. Data b => b -> b) -> Tag -> Tag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
forall u. (forall d. Data d => d -> u) -> Tag -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
$cTag :: Constr
$tTag :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapMp :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapM :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
$cgmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Tag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
dataTypeOf :: Tag -> DataType
$cdataTypeOf :: Tag -> DataType
toConstr :: Tag -> Constr
$ctoConstr :: Tag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
$cp1Data :: Typeable Tag
Data, Typeable)

instance Hashable Tag

instance IsString Tag where
  fromString :: FilePath -> Tag
fromString s :: FilePath
s = Text -> Maybe Text -> Maybe ExternalDocs -> Tag
Tag (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe Text
forall a. Maybe a
Nothing Maybe ExternalDocs
forall a. Maybe a
Nothing

-- | Allows referencing an external resource for extended documentation.
data ExternalDocs = ExternalDocs
  { -- | A short description of the target documentation.
    -- GFM syntax can be used for rich text representation.
    ExternalDocs -> Maybe Text
_externalDocsDescription :: Maybe Text

    -- | The URL for the target documentation.
  , ExternalDocs -> URL
_externalDocsUrl :: URL
  } deriving (ExternalDocs -> ExternalDocs -> Bool
(ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool) -> Eq ExternalDocs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalDocs -> ExternalDocs -> Bool
$c/= :: ExternalDocs -> ExternalDocs -> Bool
== :: ExternalDocs -> ExternalDocs -> Bool
$c== :: ExternalDocs -> ExternalDocs -> Bool
Eq, Eq ExternalDocs
Eq ExternalDocs =>
(ExternalDocs -> ExternalDocs -> Ordering)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> ExternalDocs)
-> (ExternalDocs -> ExternalDocs -> ExternalDocs)
-> Ord ExternalDocs
ExternalDocs -> ExternalDocs -> Bool
ExternalDocs -> ExternalDocs -> Ordering
ExternalDocs -> ExternalDocs -> ExternalDocs
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExternalDocs -> ExternalDocs -> ExternalDocs
$cmin :: ExternalDocs -> ExternalDocs -> ExternalDocs
max :: ExternalDocs -> ExternalDocs -> ExternalDocs
$cmax :: ExternalDocs -> ExternalDocs -> ExternalDocs
>= :: ExternalDocs -> ExternalDocs -> Bool
$c>= :: ExternalDocs -> ExternalDocs -> Bool
> :: ExternalDocs -> ExternalDocs -> Bool
$c> :: ExternalDocs -> ExternalDocs -> Bool
<= :: ExternalDocs -> ExternalDocs -> Bool
$c<= :: ExternalDocs -> ExternalDocs -> Bool
< :: ExternalDocs -> ExternalDocs -> Bool
$c< :: ExternalDocs -> ExternalDocs -> Bool
compare :: ExternalDocs -> ExternalDocs -> Ordering
$ccompare :: ExternalDocs -> ExternalDocs -> Ordering
$cp1Ord :: Eq ExternalDocs
Ord, Int -> ExternalDocs -> ShowS
[ExternalDocs] -> ShowS
ExternalDocs -> FilePath
(Int -> ExternalDocs -> ShowS)
-> (ExternalDocs -> FilePath)
-> ([ExternalDocs] -> ShowS)
-> Show ExternalDocs
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ExternalDocs] -> ShowS
$cshowList :: [ExternalDocs] -> ShowS
show :: ExternalDocs -> FilePath
$cshow :: ExternalDocs -> FilePath
showsPrec :: Int -> ExternalDocs -> ShowS
$cshowsPrec :: Int -> ExternalDocs -> ShowS
Show, (forall x. ExternalDocs -> Rep ExternalDocs x)
-> (forall x. Rep ExternalDocs x -> ExternalDocs)
-> Generic ExternalDocs
forall x. Rep ExternalDocs x -> ExternalDocs
forall x. ExternalDocs -> Rep ExternalDocs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExternalDocs x -> ExternalDocs
$cfrom :: forall x. ExternalDocs -> Rep ExternalDocs x
Generic, Typeable ExternalDocs
DataType
Constr
Typeable ExternalDocs =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ExternalDocs)
-> (ExternalDocs -> Constr)
-> (ExternalDocs -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ExternalDocs))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ExternalDocs))
-> ((forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r)
-> (forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> Data ExternalDocs
ExternalDocs -> DataType
ExternalDocs -> Constr
(forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalDocs)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs)
$cExternalDocs :: Constr
$tExternalDocs :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
gmapMp :: (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
gmapM :: (forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
gmapQi :: Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
gmapQ :: (forall d. Data d => d -> u) -> ExternalDocs -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
gmapT :: (forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs
$cgmapT :: (forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ExternalDocs)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalDocs)
dataTypeOf :: ExternalDocs -> DataType
$cdataTypeOf :: ExternalDocs -> DataType
toConstr :: ExternalDocs -> Constr
$ctoConstr :: ExternalDocs -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
$cp1Data :: Typeable ExternalDocs
Data, Typeable)

instance Hashable ExternalDocs

-- | 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.
newtype Reference = Reference { Reference -> Text
getReference :: Text }
  deriving (Reference -> Reference -> Bool
(Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool) -> Eq Reference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Reference -> Reference -> Bool
$c/= :: Reference -> Reference -> Bool
== :: Reference -> Reference -> Bool
$c== :: Reference -> Reference -> Bool
Eq, Int -> Reference -> ShowS
[Reference] -> ShowS
Reference -> FilePath
(Int -> Reference -> ShowS)
-> (Reference -> FilePath)
-> ([Reference] -> ShowS)
-> Show Reference
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Reference] -> ShowS
$cshowList :: [Reference] -> ShowS
show :: Reference -> FilePath
$cshow :: Reference -> FilePath
showsPrec :: Int -> Reference -> ShowS
$cshowsPrec :: Int -> Reference -> ShowS
Show, Typeable Reference
DataType
Constr
Typeable Reference =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Reference -> c Reference)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Reference)
-> (Reference -> Constr)
-> (Reference -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Reference))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference))
-> ((forall b. Data b => b -> b) -> Reference -> Reference)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Reference -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Reference -> r)
-> (forall u. (forall d. Data d => d -> u) -> Reference -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Reference -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Reference -> m Reference)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Reference -> m Reference)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Reference -> m Reference)
-> Data Reference
Reference -> DataType
Reference -> Constr
(forall b. Data b => b -> b) -> Reference -> Reference
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
forall u. (forall d. Data d => d -> u) -> Reference -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reference)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference)
$cReference :: Constr
$tReference :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Reference -> m Reference
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
gmapMp :: (forall d. Data d => d -> m d) -> Reference -> m Reference
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
gmapM :: (forall d. Data d => d -> m d) -> Reference -> m Reference
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
gmapQi :: Int -> (forall d. Data d => d -> u) -> Reference -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
gmapQ :: (forall d. Data d => d -> u) -> Reference -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Reference -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
gmapT :: (forall b. Data b => b -> b) -> Reference -> Reference
$cgmapT :: (forall b. Data b => b -> b) -> Reference -> Reference
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Reference)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reference)
dataTypeOf :: Reference -> DataType
$cdataTypeOf :: Reference -> DataType
toConstr :: Reference -> Constr
$ctoConstr :: Reference -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
$cp1Data :: Typeable Reference
Data, Typeable)

data Referenced a
  = Ref Reference
  | Inline a
  deriving (Referenced a -> Referenced a -> Bool
(Referenced a -> Referenced a -> Bool)
-> (Referenced a -> Referenced a -> Bool) -> Eq (Referenced a)
forall a. Eq a => Referenced a -> Referenced a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Referenced a -> Referenced a -> Bool
$c/= :: forall a. Eq a => Referenced a -> Referenced a -> Bool
== :: Referenced a -> Referenced a -> Bool
$c== :: forall a. Eq a => Referenced a -> Referenced a -> Bool
Eq, Int -> Referenced a -> ShowS
[Referenced a] -> ShowS
Referenced a -> FilePath
(Int -> Referenced a -> ShowS)
-> (Referenced a -> FilePath)
-> ([Referenced a] -> ShowS)
-> Show (Referenced a)
forall a. Show a => Int -> Referenced a -> ShowS
forall a. Show a => [Referenced a] -> ShowS
forall a. Show a => Referenced a -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Referenced a] -> ShowS
$cshowList :: forall a. Show a => [Referenced a] -> ShowS
show :: Referenced a -> FilePath
$cshow :: forall a. Show a => Referenced a -> FilePath
showsPrec :: Int -> Referenced a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Referenced a -> ShowS
Show, a -> Referenced b -> Referenced a
(a -> b) -> Referenced a -> Referenced b
(forall a b. (a -> b) -> Referenced a -> Referenced b)
-> (forall a b. a -> Referenced b -> Referenced a)
-> Functor Referenced
forall a b. a -> Referenced b -> Referenced a
forall a b. (a -> b) -> Referenced a -> Referenced b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Referenced b -> Referenced a
$c<$ :: forall a b. a -> Referenced b -> Referenced a
fmap :: (a -> b) -> Referenced a -> Referenced b
$cfmap :: forall a b. (a -> b) -> Referenced a -> Referenced b
Functor, Typeable (Referenced a)
DataType
Constr
Typeable (Referenced a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Referenced a -> c (Referenced a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Referenced a))
-> (Referenced a -> Constr)
-> (Referenced a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Referenced a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (Referenced a)))
-> ((forall b. Data b => b -> b) -> Referenced a -> Referenced a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Referenced a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Referenced a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Referenced a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Referenced a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> Data (Referenced a)
Referenced a -> DataType
Referenced a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
forall a. Data a => Typeable (Referenced a)
forall a. Data a => Referenced a -> DataType
forall a. Data a => Referenced a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Referenced a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Referenced a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Referenced a -> u
forall u. (forall d. Data d => d -> u) -> Referenced a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
$cInline :: Constr
$cRef :: Constr
$tReferenced :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
gmapMp :: (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
gmapM :: (forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Referenced a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Referenced a -> u
gmapQ :: (forall d. Data d => d -> u) -> Referenced a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Referenced a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
gmapT :: (forall b. Data b => b -> b) -> Referenced a -> Referenced a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
dataTypeOf :: Referenced a -> DataType
$cdataTypeOf :: forall a. Data a => Referenced a -> DataType
toConstr :: Referenced a -> Constr
$ctoConstr :: forall a. Data a => Referenced a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
$cp1Data :: forall a. Data a => Typeable (Referenced a)
Data, Typeable)

instance IsString a => IsString (Referenced a) where
  fromString :: FilePath -> Referenced a
fromString = a -> Referenced a
forall a. a -> Referenced a
Inline (a -> Referenced a) -> (FilePath -> a) -> FilePath -> Referenced a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> a
forall a. IsString a => FilePath -> a
fromString

newtype URL = URL { URL -> Text
getUrl :: Text } deriving (URL -> URL -> Bool
(URL -> URL -> Bool) -> (URL -> URL -> Bool) -> Eq URL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: URL -> URL -> Bool
$c/= :: URL -> URL -> Bool
== :: URL -> URL -> Bool
$c== :: URL -> URL -> Bool
Eq, Eq URL
Eq URL =>
(URL -> URL -> Ordering)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> URL)
-> (URL -> URL -> URL)
-> Ord URL
URL -> URL -> Bool
URL -> URL -> Ordering
URL -> URL -> URL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: URL -> URL -> URL
$cmin :: URL -> URL -> URL
max :: URL -> URL -> URL
$cmax :: URL -> URL -> URL
>= :: URL -> URL -> Bool
$c>= :: URL -> URL -> Bool
> :: URL -> URL -> Bool
$c> :: URL -> URL -> Bool
<= :: URL -> URL -> Bool
$c<= :: URL -> URL -> Bool
< :: URL -> URL -> Bool
$c< :: URL -> URL -> Bool
compare :: URL -> URL -> Ordering
$ccompare :: URL -> URL -> Ordering
$cp1Ord :: Eq URL
Ord, Int -> URL -> ShowS
[URL] -> ShowS
URL -> FilePath
(Int -> URL -> ShowS)
-> (URL -> FilePath) -> ([URL] -> ShowS) -> Show URL
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [URL] -> ShowS
$cshowList :: [URL] -> ShowS
show :: URL -> FilePath
$cshow :: URL -> FilePath
showsPrec :: Int -> URL -> ShowS
$cshowsPrec :: Int -> URL -> ShowS
Show, Int -> URL -> Int
URL -> Int
(Int -> URL -> Int) -> (URL -> Int) -> Hashable URL
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: URL -> Int
$chash :: URL -> Int
hashWithSalt :: Int -> URL -> Int
$chashWithSalt :: Int -> URL -> Int
Hashable, [URL] -> Encoding
[URL] -> Value
URL -> Encoding
URL -> Value
(URL -> Value)
-> (URL -> Encoding)
-> ([URL] -> Value)
-> ([URL] -> Encoding)
-> ToJSON URL
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [URL] -> Encoding
$ctoEncodingList :: [URL] -> Encoding
toJSONList :: [URL] -> Value
$ctoJSONList :: [URL] -> Value
toEncoding :: URL -> Encoding
$ctoEncoding :: URL -> Encoding
toJSON :: URL -> Value
$ctoJSON :: URL -> Value
ToJSON, Value -> Parser [URL]
Value -> Parser URL
(Value -> Parser URL) -> (Value -> Parser [URL]) -> FromJSON URL
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [URL]
$cparseJSONList :: Value -> Parser [URL]
parseJSON :: Value -> Parser URL
$cparseJSON :: Value -> Parser URL
FromJSON, Typeable URL
DataType
Constr
Typeable URL =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> URL -> c URL)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c URL)
-> (URL -> Constr)
-> (URL -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c URL))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL))
-> ((forall b. Data b => b -> b) -> URL -> URL)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r)
-> (forall u. (forall d. Data d => d -> u) -> URL -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> URL -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> URL -> m URL)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> URL -> m URL)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> URL -> m URL)
-> Data URL
URL -> DataType
URL -> Constr
(forall b. Data b => b -> b) -> URL -> URL
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
forall u. (forall d. Data d => d -> u) -> URL -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> URL -> m URL
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c URL)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL)
$cURL :: Constr
$tURL :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> URL -> m URL
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL
gmapMp :: (forall d. Data d => d -> m d) -> URL -> m URL
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL
gmapM :: (forall d. Data d => d -> m d) -> URL -> m URL
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> URL -> m URL
gmapQi :: Int -> (forall d. Data d => d -> u) -> URL -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
gmapQ :: (forall d. Data d => d -> u) -> URL -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> URL -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
gmapT :: (forall b. Data b => b -> b) -> URL -> URL
$cgmapT :: (forall b. Data b => b -> b) -> URL -> URL
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c URL)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c URL)
dataTypeOf :: URL -> DataType
$cdataTypeOf :: URL -> DataType
toConstr :: URL -> Constr
$ctoConstr :: URL -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
$cp1Data :: Typeable URL
Data, Typeable)

data AdditionalProperties
  = AdditionalPropertiesAllowed Bool
  | AdditionalPropertiesSchema (Referenced Schema)
  deriving (AdditionalProperties -> AdditionalProperties -> Bool
(AdditionalProperties -> AdditionalProperties -> Bool)
-> (AdditionalProperties -> AdditionalProperties -> Bool)
-> Eq AdditionalProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdditionalProperties -> AdditionalProperties -> Bool
$c/= :: AdditionalProperties -> AdditionalProperties -> Bool
== :: AdditionalProperties -> AdditionalProperties -> Bool
$c== :: AdditionalProperties -> AdditionalProperties -> Bool
Eq, Int -> AdditionalProperties -> ShowS
[AdditionalProperties] -> ShowS
AdditionalProperties -> FilePath
(Int -> AdditionalProperties -> ShowS)
-> (AdditionalProperties -> FilePath)
-> ([AdditionalProperties] -> ShowS)
-> Show AdditionalProperties
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [AdditionalProperties] -> ShowS
$cshowList :: [AdditionalProperties] -> ShowS
show :: AdditionalProperties -> FilePath
$cshow :: AdditionalProperties -> FilePath
showsPrec :: Int -> AdditionalProperties -> ShowS
$cshowsPrec :: Int -> AdditionalProperties -> ShowS
Show, Typeable AdditionalProperties
DataType
Constr
Typeable AdditionalProperties =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> AdditionalProperties
 -> c AdditionalProperties)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c AdditionalProperties)
-> (AdditionalProperties -> Constr)
-> (AdditionalProperties -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c AdditionalProperties))
-> ((forall b. Data b => b -> b)
    -> AdditionalProperties -> AdditionalProperties)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> AdditionalProperties -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> AdditionalProperties -> m AdditionalProperties)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> AdditionalProperties -> m AdditionalProperties)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> AdditionalProperties -> m AdditionalProperties)
-> Data AdditionalProperties
AdditionalProperties -> DataType
AdditionalProperties -> Constr
(forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties)
$cAdditionalPropertiesSchema :: Constr
$cAdditionalPropertiesAllowed :: Constr
$tAdditionalProperties :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
gmapMp :: (forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
gmapM :: (forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
gmapQi :: Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
gmapQ :: (forall d. Data d => d -> u) -> AdditionalProperties -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
gmapT :: (forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties
$cgmapT :: (forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties)
dataTypeOf :: AdditionalProperties -> DataType
$cdataTypeOf :: AdditionalProperties -> DataType
toConstr :: AdditionalProperties -> Constr
$ctoConstr :: AdditionalProperties -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
$cp1Data :: Typeable AdditionalProperties
Data, Typeable)

-------------------------------------------------------------------------------
-- Generic instances
-------------------------------------------------------------------------------

deriveGeneric ''Header
deriveGeneric ''OAuth2Params
deriveGeneric ''Operation
deriveGeneric ''Param
deriveGeneric ''ParamOtherSchema
deriveGeneric ''PathItem
deriveGeneric ''Response
deriveGeneric ''Responses
deriveGeneric ''SecurityScheme
deriveGeneric ''Schema
deriveGeneric ''ParamSchema
deriveGeneric ''Swagger

-- =======================================================================
-- Monoid instances
-- =======================================================================

instance Semigroup Swagger where
  <> :: Swagger -> Swagger -> Swagger
(<>) = Swagger -> Swagger -> Swagger
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Swagger where
  mempty :: Swagger
mempty = Swagger
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Swagger -> Swagger -> Swagger
mappend = Swagger -> Swagger -> Swagger
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Info where
  <> :: Info -> Info -> Info
(<>) = Info -> Info -> Info
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Info where
  mempty :: Info
mempty = Info
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Info -> Info -> Info
mappend = Info -> Info -> Info
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Contact where
  <> :: Contact -> Contact -> Contact
(<>) = Contact -> Contact -> Contact
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Contact where
  mempty :: Contact
mempty = Contact
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Contact -> Contact -> Contact
mappend = Contact -> Contact -> Contact
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup PathItem where
  <> :: PathItem -> PathItem -> PathItem
(<>) = PathItem -> PathItem -> PathItem
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid PathItem where
  mempty :: PathItem
mempty = PathItem
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: PathItem -> PathItem -> PathItem
mappend = PathItem -> PathItem -> PathItem
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Schema where
  <> :: Schema -> Schema -> Schema
(<>) = Schema -> Schema -> Schema
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Schema where
  mempty :: Schema
mempty = Schema
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Schema -> Schema -> Schema
mappend = Schema -> Schema -> Schema
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup (ParamSchema t) where
  <> :: ParamSchema t -> ParamSchema t -> ParamSchema t
(<>) = ParamSchema t -> ParamSchema t -> ParamSchema t
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid (ParamSchema t) where
  mempty :: ParamSchema t
mempty = ParamSchema t
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: ParamSchema t -> ParamSchema t -> ParamSchema t
mappend = ParamSchema t -> ParamSchema t -> ParamSchema t
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Param where
  <> :: Param -> Param -> Param
(<>) = Param -> Param -> Param
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Param where
  mempty :: Param
mempty = Param
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Param -> Param -> Param
mappend = Param -> Param -> Param
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup ParamOtherSchema where
  <> :: ParamOtherSchema -> ParamOtherSchema -> ParamOtherSchema
(<>) = ParamOtherSchema -> ParamOtherSchema -> ParamOtherSchema
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid ParamOtherSchema where
  mempty :: ParamOtherSchema
mempty = ParamOtherSchema
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: ParamOtherSchema -> ParamOtherSchema -> ParamOtherSchema
mappend = ParamOtherSchema -> ParamOtherSchema -> ParamOtherSchema
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Header where
  <> :: Header -> Header -> Header
(<>) = Header -> Header -> Header
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Header where
  mempty :: Header
mempty = Header
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Header -> Header -> Header
mappend = Header -> Header -> Header
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Responses where
  <> :: Responses -> Responses -> Responses
(<>) = Responses -> Responses -> Responses
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Responses where
  mempty :: Responses
mempty = Responses
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Responses -> Responses -> Responses
mappend = Responses -> Responses -> Responses
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Response where
  <> :: Response -> Response -> Response
(<>) = Response -> Response -> Response
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Response where
  mempty :: Response
mempty = Response
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Response -> Response -> Response
mappend = Response -> Response -> Response
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup ExternalDocs where
  <> :: ExternalDocs -> ExternalDocs -> ExternalDocs
(<>) = ExternalDocs -> ExternalDocs -> ExternalDocs
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid ExternalDocs where
  mempty :: ExternalDocs
mempty = ExternalDocs
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: ExternalDocs -> ExternalDocs -> ExternalDocs
mappend = ExternalDocs -> ExternalDocs -> ExternalDocs
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Operation where
  <> :: Operation -> Operation -> Operation
(<>) = Operation -> Operation -> Operation
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Operation where
  mempty :: Operation
mempty = Operation
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Operation -> Operation -> Operation
mappend = Operation -> Operation -> Operation
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Example where
  <> :: Example -> Example -> Example
(<>) = Example -> Example -> Example
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Example where
  mempty :: Example
mempty = Example
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Example -> Example -> Example
mappend = Example -> Example -> Example
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup SecurityScheme where
  <> :: SecurityScheme -> SecurityScheme -> SecurityScheme
(<>) = SecurityScheme -> SecurityScheme -> SecurityScheme
mergeSecurityScheme

instance Semigroup SecurityDefinitions where
  (SecurityDefinitions sd1 :: Definitions SecurityScheme
sd1) <> :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
<> (SecurityDefinitions sd2 :: Definitions SecurityScheme
sd2) =
     Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions (Definitions SecurityScheme -> SecurityDefinitions)
-> Definitions SecurityScheme -> SecurityDefinitions
forall a b. (a -> b) -> a -> b
$ (SecurityScheme -> SecurityScheme -> SecurityScheme)
-> Definitions SecurityScheme
-> Definitions SecurityScheme
-> Definitions SecurityScheme
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith SecurityScheme -> SecurityScheme -> SecurityScheme
forall a. Semigroup a => a -> a -> a
(<>) Definitions SecurityScheme
sd1 Definitions SecurityScheme
sd2

instance Monoid SecurityDefinitions where
  mempty :: SecurityDefinitions
mempty = Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions Definitions SecurityScheme
forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
  mappend :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
mappend = SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
forall a. Semigroup a => a -> a -> a
(<>)

-- =======================================================================
-- SwaggerMonoid helper instances
-- =======================================================================

instance SwaggerMonoid Info
instance SwaggerMonoid PathItem
instance SwaggerMonoid Schema
instance SwaggerMonoid (ParamSchema t)
instance SwaggerMonoid Param
instance SwaggerMonoid ParamOtherSchema
instance SwaggerMonoid Responses
instance SwaggerMonoid Response
instance SwaggerMonoid ExternalDocs
instance SwaggerMonoid Operation
instance SwaggerMonoid SecurityDefinitions
instance (Eq a, Hashable a) => SwaggerMonoid (InsOrdHashSet a)

instance SwaggerMonoid MimeList
deriving instance SwaggerMonoid URL

instance SwaggerMonoid (SwaggerType t) where
  swaggerMempty :: SwaggerType t
swaggerMempty = SwaggerType t
forall (t :: SwaggerKind *). SwaggerType t
SwaggerString
  swaggerMappend :: SwaggerType t -> SwaggerType t -> SwaggerType t
swaggerMappend _ y :: SwaggerType t
y = SwaggerType t
y

instance SwaggerMonoid ParamLocation where
  swaggerMempty :: ParamLocation
swaggerMempty = ParamLocation
ParamQuery
  swaggerMappend :: ParamLocation -> ParamLocation -> ParamLocation
swaggerMappend _ y :: ParamLocation
y = ParamLocation
y

instance {-# OVERLAPPING #-} SwaggerMonoid (InsOrdHashMap FilePath PathItem) where
  swaggerMempty :: InsOrdHashMap FilePath PathItem
swaggerMempty = InsOrdHashMap FilePath PathItem
forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
  swaggerMappend :: InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
swaggerMappend = (PathItem -> PathItem -> PathItem)
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith PathItem -> PathItem -> PathItem
forall a. Monoid a => a -> a -> a
mappend

instance Monoid a => SwaggerMonoid (Referenced a) where
  swaggerMempty :: Referenced a
swaggerMempty = a -> Referenced a
forall a. a -> Referenced a
Inline a
forall a. Monoid a => a
mempty
  swaggerMappend :: Referenced a -> Referenced a -> Referenced a
swaggerMappend (Inline x :: a
x) (Inline y :: a
y) = a -> Referenced a
forall a. a -> Referenced a
Inline (a -> a -> a
forall a. Monoid a => a -> a -> a
mappend a
x a
y)
  swaggerMappend _ y :: Referenced a
y = Referenced a
y

instance SwaggerMonoid ParamAnySchema where
  swaggerMempty :: ParamAnySchema
swaggerMempty = ParamOtherSchema -> ParamAnySchema
ParamOther ParamOtherSchema
forall m. SwaggerMonoid m => m
swaggerMempty
  swaggerMappend :: ParamAnySchema -> ParamAnySchema -> ParamAnySchema
swaggerMappend (ParamBody x :: Referenced Schema
x) (ParamBody y :: Referenced Schema
y) = Referenced Schema -> ParamAnySchema
ParamBody (Referenced Schema -> Referenced Schema -> Referenced Schema
forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Referenced Schema
x Referenced Schema
y)
  swaggerMappend (ParamOther x :: ParamOtherSchema
x) (ParamOther y :: ParamOtherSchema
y) = ParamOtherSchema -> ParamAnySchema
ParamOther (ParamOtherSchema -> ParamOtherSchema -> ParamOtherSchema
forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend ParamOtherSchema
x ParamOtherSchema
y)
  swaggerMappend _ y :: ParamAnySchema
y = ParamAnySchema
y

-- =======================================================================
-- Simple Generic-based ToJSON instances
-- =======================================================================

instance ToJSON ParamLocation where
  toJSON :: ParamLocation -> Value
toJSON = Options -> ParamLocation -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "Param")

instance ToJSON Info where
  toJSON :: Info -> Value
toJSON = Options -> Info -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "Info")

instance ToJSON Contact where
  toJSON :: Contact -> Value
toJSON = Options -> Contact -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "Contact")

instance ToJSON License where
  toJSON :: License -> Value
toJSON = Options -> License -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "License")

instance ToJSON ApiKeyLocation where
  toJSON :: ApiKeyLocation -> Value
toJSON = Options -> ApiKeyLocation -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "ApiKey")

instance ToJSON ApiKeyParams where
  toJSON :: ApiKeyParams -> Value
toJSON = Options -> ApiKeyParams -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "apiKey")

instance ToJSON Scheme where
  toJSON :: Scheme -> Value
toJSON = Options -> Scheme -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "")

instance ToJSON Tag where
  toJSON :: Tag -> Value
toJSON = Options -> Tag -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "Tag")

instance ToJSON ExternalDocs where
  toJSON :: ExternalDocs -> Value
toJSON = Options -> ExternalDocs -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "ExternalDocs")

instance ToJSON Xml where
  toJSON :: Xml -> Value
toJSON = Options -> Xml -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix "Xml")

-- =======================================================================
-- Simple Generic-based FromJSON instances
-- =======================================================================

instance FromJSON ParamLocation where
  parseJSON :: Value -> Parser ParamLocation
parseJSON = Options -> Value -> Parser ParamLocation
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "Param")

instance FromJSON Info where
  parseJSON :: Value -> Parser Info
parseJSON = Options -> Value -> Parser Info
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "Info")

instance FromJSON Contact where
  parseJSON :: Value -> Parser Contact
parseJSON = Options -> Value -> Parser Contact
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "Contact")

instance FromJSON License where
  parseJSON :: Value -> Parser License
parseJSON = Options -> Value -> Parser License
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "License")

instance FromJSON ApiKeyLocation where
  parseJSON :: Value -> Parser ApiKeyLocation
parseJSON = Options -> Value -> Parser ApiKeyLocation
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "ApiKey")

instance FromJSON ApiKeyParams where
  parseJSON :: Value -> Parser ApiKeyParams
parseJSON = Options -> Value -> Parser ApiKeyParams
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "apiKey")

instance FromJSON Scheme where
  parseJSON :: Value -> Parser Scheme
parseJSON = Options -> Value -> Parser Scheme
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "")

instance FromJSON Tag where
  parseJSON :: Value -> Parser Tag
parseJSON = Options -> Value -> Parser Tag
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "Tag")

instance FromJSON ExternalDocs where
  parseJSON :: Value -> Parser ExternalDocs
parseJSON = Options -> Value -> Parser ExternalDocs
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "ExternalDocs")

-- =======================================================================
-- Manual ToJSON instances
-- =======================================================================

instance ToJSON OAuth2Flow where
  toJSON :: OAuth2Flow -> Value
toJSON (OAuth2Implicit authUrl :: Text
authUrl) = [Pair] -> Value
object
    [ "flow"             Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("implicit" :: Text)
    , "authorizationUrl" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
authUrl ]
  toJSON (OAuth2Password tokenUrl :: Text
tokenUrl) = [Pair] -> Value
object
    [ "flow"     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("password" :: Text)
    , "tokenUrl" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
tokenUrl ]
  toJSON (OAuth2Application tokenUrl :: Text
tokenUrl) = [Pair] -> Value
object
    [ "flow"     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("application" :: Text)
    , "tokenUrl" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
tokenUrl ]
  toJSON (OAuth2AccessCode authUrl :: Text
authUrl tokenUrl :: Text
tokenUrl) = [Pair] -> Value
object
    [ "flow"             Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("accessCode" :: Text)
    , "authorizationUrl" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
authUrl
    , "tokenUrl"         Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
tokenUrl ]

instance ToJSON OAuth2Params where
  toJSON :: OAuth2Params -> Value
toJSON = OAuth2Params -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: OAuth2Params -> Encoding
toEncoding = OAuth2Params -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON SecuritySchemeType where
  toJSON :: SecuritySchemeType -> Value
toJSON SecuritySchemeBasic
      = [Pair] -> Value
object [ "type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("basic" :: Text) ]
  toJSON (SecuritySchemeApiKey params :: ApiKeyParams
params)
      = ApiKeyParams -> Value
forall a. ToJSON a => a -> Value
toJSON ApiKeyParams
params
    Value -> Value -> Value
<+> [Pair] -> Value
object [ "type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("apiKey" :: Text) ]
  toJSON (SecuritySchemeOAuth2 params :: OAuth2Params
params)
      = OAuth2Params -> Value
forall a. ToJSON a => a -> Value
toJSON OAuth2Params
params
    Value -> Value -> Value
<+> [Pair] -> Value
object [ "type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("oauth2" :: Text) ]

instance ToJSON Swagger where
  toJSON :: Swagger -> Value
toJSON a :: Swagger
a = Swagger -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON Swagger
a Value -> (Value -> Value) -> Value
forall a b. a -> (a -> b) -> b
&
    if InsOrdHashMap FilePath PathItem -> Bool
forall k v. InsOrdHashMap k v -> Bool
InsOrdHashMap.null (Swagger -> InsOrdHashMap FilePath PathItem
_swaggerPaths Swagger
a)
    then (Value -> Value -> Value
<+> [Pair] -> Value
object ["paths" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object []])
    else Value -> Value
forall a. a -> a
id
  toEncoding :: Swagger -> Encoding
toEncoding = Swagger -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON SecurityScheme where
  toJSON :: SecurityScheme -> Value
toJSON = SecurityScheme -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: SecurityScheme -> Encoding
toEncoding = SecurityScheme -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Schema where
  toJSON :: Schema -> Value
toJSON = Schema -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Schema -> Encoding
toEncoding = Schema -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Header where
  toJSON :: Header -> Value
toJSON = Header -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Header -> Encoding
toEncoding = Header -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

-- | As for nullary schema for 0-arity type constructors, see
-- <https://github.com/GetShopTV/swagger2/issues/167>.
--
-- >>> encode (SwaggerItemsArray [])
-- "{\"example\":[],\"items\":{},\"maxItems\":0}"
--
instance ToJSON (ParamSchema t) => ToJSON (SwaggerItems t) where
  toJSON :: SwaggerItems t -> Value
toJSON (SwaggerItemsPrimitive fmt :: Maybe (CollectionFormat t)
fmt schema :: ParamSchema t
schema) = [Pair] -> Value
object
    [ "collectionFormat" Key -> Maybe (CollectionFormat t) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe (CollectionFormat t)
fmt
    , "items"            Key -> ParamSchema t -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ParamSchema t
schema ]
  toJSON (SwaggerItemsObject x :: Referenced Schema
x) = [Pair] -> Value
object [ "items" Key -> Referenced Schema -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Referenced Schema
x ]
  toJSON (SwaggerItemsArray  []) = [Pair] -> Value
object
    [ "items" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object []
    , "maxItems" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (0 :: Int)
    , "example" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Array -> Value
Array Array
forall a. Monoid a => a
mempty
    ]
  toJSON (SwaggerItemsArray  x :: [Referenced Schema]
x) = [Pair] -> Value
object [ "items" Key -> [Referenced Schema] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Referenced Schema]
x ]

instance ToJSON Host where
  toJSON :: Host -> Value
toJSON (Host host :: FilePath
host mport :: Maybe PortNumber
mport) = FilePath -> Value
forall a. ToJSON a => a -> Value
toJSON (FilePath -> Value) -> FilePath -> Value
forall a b. (a -> b) -> a -> b
$
    case Maybe PortNumber
mport of
      Nothing -> FilePath
host
      Just port :: PortNumber
port -> FilePath
host FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ ":" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ PortNumber -> FilePath
forall a. Show a => a -> FilePath
show PortNumber
port

instance ToJSON MimeList where
  toJSON :: MimeList -> Value
toJSON (MimeList xs :: [MediaType]
xs) = [FilePath] -> Value
forall a. ToJSON a => a -> Value
toJSON ((MediaType -> FilePath) -> [MediaType] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map MediaType -> FilePath
forall a. Show a => a -> FilePath
show [MediaType]
xs)

instance ToJSON Param where
  toJSON :: Param -> Value
toJSON = Param -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Param -> Encoding
toEncoding = Param -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON ParamAnySchema where
  toJSON :: ParamAnySchema -> Value
toJSON (ParamBody s :: Referenced Schema
s) = [Pair] -> Value
object [ "in" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ("body" :: Text), "schema" Key -> Referenced Schema -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Referenced Schema
s ]
  toJSON (ParamOther s :: ParamOtherSchema
s) = ParamOtherSchema -> Value
forall a. ToJSON a => a -> Value
toJSON ParamOtherSchema
s

instance ToJSON ParamOtherSchema where
  toJSON :: ParamOtherSchema -> Value
toJSON = ParamOtherSchema -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: ParamOtherSchema -> Encoding
toEncoding = ParamOtherSchema -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Responses where
  toJSON :: Responses -> Value
toJSON = Responses -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Responses -> Encoding
toEncoding = Responses -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Response where
  toJSON :: Response -> Value
toJSON = Response -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Response -> Encoding
toEncoding = Response -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Operation where
  toJSON :: Operation -> Value
toJSON = Operation -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Operation -> Encoding
toEncoding = Operation -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON PathItem where
  toJSON :: PathItem -> Value
toJSON = PathItem -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: PathItem -> Encoding
toEncoding = PathItem -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Example where
  toJSON :: Example -> Value
toJSON = Map FilePath Value -> Value
forall a. ToJSON a => a -> Value
toJSON (Map FilePath Value -> Value)
-> (Example -> Map FilePath Value) -> Example -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MediaType -> FilePath)
-> Map MediaType Value -> Map FilePath Value
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys MediaType -> FilePath
forall a. Show a => a -> FilePath
show (Map MediaType Value -> Map FilePath Value)
-> (Example -> Map MediaType Value)
-> Example
-> Map FilePath Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> Map MediaType Value
getExample

instance ToJSON SecurityDefinitions where
  toJSON :: SecurityDefinitions -> Value
toJSON (SecurityDefinitions sd :: Definitions SecurityScheme
sd) = Definitions SecurityScheme -> Value
forall a. ToJSON a => a -> Value
toJSON Definitions SecurityScheme
sd

instance ToJSON Reference where
  toJSON :: Reference -> Value
toJSON (Reference ref :: Text
ref) = [Pair] -> Value
object [ "$ref" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
ref ]

referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
referencedToJSON :: Text -> Referenced a -> Value
referencedToJSON prefix :: Text
prefix (Ref (Reference ref :: Text
ref)) = [Pair] -> Value
object [ "$ref" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref) ]
referencedToJSON _ (Inline x :: a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x

instance ToJSON (Referenced Schema)   where toJSON :: Referenced Schema -> Value
toJSON = Text -> Referenced Schema -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON "#/definitions/"
instance ToJSON (Referenced Param)    where toJSON :: Referenced Param -> Value
toJSON = Text -> Referenced Param -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON "#/parameters/"
instance ToJSON (Referenced Response) where toJSON :: Referenced Response -> Value
toJSON = Text -> Referenced Response -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON "#/responses/"

instance ToJSON (SwaggerType t) where
  toJSON :: SwaggerType t -> Value
toJSON SwaggerArray   = "array"
  toJSON SwaggerString  = "string"
  toJSON SwaggerInteger = "integer"
  toJSON SwaggerNumber  = "number"
  toJSON SwaggerBoolean = "boolean"
  toJSON SwaggerFile    = "file"
  toJSON SwaggerNull    = "null"
  toJSON SwaggerObject  = "object"

instance ToJSON (CollectionFormat t) where
  toJSON :: CollectionFormat t -> Value
toJSON CollectionCSV   = "csv"
  toJSON CollectionSSV   = "ssv"
  toJSON CollectionTSV   = "tsv"
  toJSON CollectionPipes = "pipes"
  toJSON CollectionMulti = "multi"

instance ToJSON (ParamSchema k) where
  -- TODO: this is a bit fishy, why we need sub object only in `ToJSON`?
  toJSON :: ParamSchema k -> Value
toJSON = SwaggerAesonOptions -> ParamSchema k -> Value
forall a (xs :: [*]).
(Generic a, All2 AesonDefaultValue (Code a), HasDatatypeInfo a,
 All2 ToJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
SwaggerAesonOptions -> a -> Value
sopSwaggerGenericToJSONWithOpts (SwaggerAesonOptions -> ParamSchema k -> Value)
-> SwaggerAesonOptions -> ParamSchema k -> Value
forall a b. (a -> b) -> a -> b
$
      FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "paramSchema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "items"

instance ToJSON AdditionalProperties where
  toJSON :: AdditionalProperties -> Value
toJSON (AdditionalPropertiesAllowed b :: Bool
b) = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
b
  toJSON (AdditionalPropertiesSchema s :: Referenced Schema
s) = Referenced Schema -> Value
forall a. ToJSON a => a -> Value
toJSON Referenced Schema
s

-- =======================================================================
-- Manual FromJSON instances
-- =======================================================================

instance FromJSON OAuth2Flow where
  parseJSON :: Value -> Parser OAuth2Flow
parseJSON (Object o :: Object
o) = do
    (Text
flow :: Text) <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "flow"
    case Text
flow of
      "implicit"    -> Text -> OAuth2Flow
OAuth2Implicit    (Text -> OAuth2Flow) -> Parser Text -> Parser OAuth2Flow
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "authorizationUrl"
      "password"    -> Text -> OAuth2Flow
OAuth2Password    (Text -> OAuth2Flow) -> Parser Text -> Parser OAuth2Flow
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "tokenUrl"
      "application" -> Text -> OAuth2Flow
OAuth2Application (Text -> OAuth2Flow) -> Parser Text -> Parser OAuth2Flow
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "tokenUrl"
      "accessCode"  -> Text -> Text -> OAuth2Flow
OAuth2AccessCode
        (Text -> Text -> OAuth2Flow)
-> Parser Text -> Parser (Text -> OAuth2Flow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "authorizationUrl"
        Parser (Text -> OAuth2Flow) -> Parser Text -> Parser OAuth2Flow
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "tokenUrl"
      _ -> Parser OAuth2Flow
forall (f :: * -> *) a. Alternative f => f a
empty
  parseJSON _ = Parser OAuth2Flow
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON OAuth2Params where
  parseJSON :: Value -> Parser OAuth2Params
parseJSON = Value -> Parser OAuth2Params
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON SecuritySchemeType where
  parseJSON :: Value -> Parser SecuritySchemeType
parseJSON js :: Value
js@(Object o :: Object
o) = do
    (Text
t :: Text) <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "type"
    case Text
t of
      "basic"  -> SecuritySchemeType -> Parser SecuritySchemeType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SecuritySchemeType
SecuritySchemeBasic
      "apiKey" -> ApiKeyParams -> SecuritySchemeType
SecuritySchemeApiKey (ApiKeyParams -> SecuritySchemeType)
-> Parser ApiKeyParams -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ApiKeyParams
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
      "oauth2" -> OAuth2Params -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Params -> SecuritySchemeType)
-> Parser OAuth2Params -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser OAuth2Params
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
      _ -> Parser SecuritySchemeType
forall (f :: * -> *) a. Alternative f => f a
empty
  parseJSON _ = Parser SecuritySchemeType
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON Swagger where
  parseJSON :: Value -> Parser Swagger
parseJSON = Value -> Parser Swagger
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON SecurityScheme where
  parseJSON :: Value -> Parser SecurityScheme
parseJSON = Value -> Parser SecurityScheme
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON Schema where
  parseJSON :: Value -> Parser Schema
parseJSON = (Schema -> Schema) -> Parser Schema -> Parser Schema
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Schema -> Schema
nullaryCleanup (Parser Schema -> Parser Schema)
-> (Value -> Parser Schema) -> Value -> Parser Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Schema
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
    where nullaryCleanup :: Schema -> Schema
          nullaryCleanup :: Schema -> Schema
nullaryCleanup s :: Schema
s@Schema{_schemaParamSchema :: Schema -> ParamSchema 'SwaggerKindSchema
_schemaParamSchema=ParamSchema 'SwaggerKindSchema
ps} =
            if ParamSchema 'SwaggerKindSchema
-> Maybe (SwaggerItems 'SwaggerKindSchema)
forall (t :: SwaggerKind *).
ParamSchema t -> Maybe (SwaggerItems t)
_paramSchemaItems ParamSchema 'SwaggerKindSchema
ps Maybe (SwaggerItems 'SwaggerKindSchema)
-> Maybe (SwaggerItems 'SwaggerKindSchema) -> Bool
forall a. Eq a => a -> a -> Bool
== SwaggerItems 'SwaggerKindSchema
-> Maybe (SwaggerItems 'SwaggerKindSchema)
forall a. a -> Maybe a
Just ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsArray [])
              then Schema
s { _schemaExample :: Maybe Value
_schemaExample = Maybe Value
forall a. Maybe a
Nothing
                     , _schemaParamSchema :: ParamSchema 'SwaggerKindSchema
_schemaParamSchema = ParamSchema 'SwaggerKindSchema
ps { _paramSchemaMaxItems :: Maybe Integer
_paramSchemaMaxItems = Maybe Integer
forall a. Maybe a
Nothing } }
              else Schema
s

instance FromJSON Header where
  parseJSON :: Value -> Parser Header
parseJSON = Value -> Parser Header
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance (FromJSON (CollectionFormat ('SwaggerKindNormal t)), FromJSON (ParamSchema ('SwaggerKindNormal t))) => FromJSON (SwaggerItems ('SwaggerKindNormal t)) where
  parseJSON :: Value -> Parser (SwaggerItems ('SwaggerKindNormal t))
parseJSON = FilePath
-> (Object -> Parser (SwaggerItems ('SwaggerKindNormal t)))
-> Value
-> Parser (SwaggerItems ('SwaggerKindNormal t))
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject "SwaggerItemsPrimitive" ((Object -> Parser (SwaggerItems ('SwaggerKindNormal t)))
 -> Value -> Parser (SwaggerItems ('SwaggerKindNormal t)))
-> (Object -> Parser (SwaggerItems ('SwaggerKindNormal t)))
-> Value
-> Parser (SwaggerItems ('SwaggerKindNormal t))
forall a b. (a -> b) -> a -> b
$ \o :: Object
o -> Maybe (CollectionFormat ('SwaggerKindNormal t))
-> ParamSchema ('SwaggerKindNormal t)
-> SwaggerItems ('SwaggerKindNormal t)
forall (k :: SwaggerKind *).
Maybe (CollectionFormat k) -> ParamSchema k -> SwaggerItems k
SwaggerItemsPrimitive
    (Maybe (CollectionFormat ('SwaggerKindNormal t))
 -> ParamSchema ('SwaggerKindNormal t)
 -> SwaggerItems ('SwaggerKindNormal t))
-> Parser (Maybe (CollectionFormat ('SwaggerKindNormal t)))
-> Parser
     (ParamSchema ('SwaggerKindNormal t)
      -> SwaggerItems ('SwaggerKindNormal t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object
-> Key -> Parser (Maybe (CollectionFormat ('SwaggerKindNormal t)))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? "collectionFormat"
    Parser
  (ParamSchema ('SwaggerKindNormal t)
   -> SwaggerItems ('SwaggerKindNormal t))
-> Parser (ParamSchema ('SwaggerKindNormal t))
-> Parser (SwaggerItems ('SwaggerKindNormal t))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: "items" Parser Value
-> (Value -> Parser (ParamSchema ('SwaggerKindNormal t)))
-> Parser (ParamSchema ('SwaggerKindNormal t))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser (ParamSchema ('SwaggerKindNormal t))
forall a. FromJSON a => Value -> Parser a
parseJSON)

instance FromJSON (SwaggerItems 'SwaggerKindParamOtherSchema) where
  parseJSON :: Value -> Parser (SwaggerItems 'SwaggerKindParamOtherSchema)
parseJSON = FilePath
-> (Object -> Parser (SwaggerItems 'SwaggerKindParamOtherSchema))
-> Value
-> Parser (SwaggerItems 'SwaggerKindParamOtherSchema)
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject "SwaggerItemsPrimitive" ((Object -> Parser (SwaggerItems 'SwaggerKindParamOtherSchema))
 -> Value -> Parser (SwaggerItems 'SwaggerKindParamOtherSchema))
-> (Object -> Parser (SwaggerItems 'SwaggerKindParamOtherSchema))
-> Value
-> Parser (SwaggerItems 'SwaggerKindParamOtherSchema)
forall a b. (a -> b) -> a -> b
$ \o :: Object
o -> Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
-> ParamSchema 'SwaggerKindParamOtherSchema
-> SwaggerItems 'SwaggerKindParamOtherSchema
forall (k :: SwaggerKind *).
Maybe (CollectionFormat k) -> ParamSchema k -> SwaggerItems k
SwaggerItemsPrimitive
    (Maybe (CollectionFormat 'SwaggerKindParamOtherSchema)
 -> ParamSchema 'SwaggerKindParamOtherSchema
 -> SwaggerItems 'SwaggerKindParamOtherSchema)
-> Parser (Maybe (CollectionFormat 'SwaggerKindParamOtherSchema))
-> Parser
     (ParamSchema 'SwaggerKindParamOtherSchema
      -> SwaggerItems 'SwaggerKindParamOtherSchema)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object
-> Key
-> Parser (Maybe (CollectionFormat 'SwaggerKindParamOtherSchema))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? "collectionFormat"
    Parser
  (ParamSchema 'SwaggerKindParamOtherSchema
   -> SwaggerItems 'SwaggerKindParamOtherSchema)
-> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
-> Parser (SwaggerItems 'SwaggerKindParamOtherSchema)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: "items" Parser Value
-> (Value -> Parser (ParamSchema 'SwaggerKindParamOtherSchema))
-> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
forall a. FromJSON a => Value -> Parser a
parseJSON) Parser (ParamSchema 'SwaggerKindParamOtherSchema)
-> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
-> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FilePath -> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail ("foo" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Object -> FilePath
forall a. Show a => a -> FilePath
show Object
o))

-- |
--
-- >>> decode "{}" :: Maybe (SwaggerItems 'SwaggerKindSchema)
-- Just (SwaggerItemsArray [])
--
-- >>> eitherDecode "{\"$ref\":\"#/definitions/example\"}" :: Either String (SwaggerItems 'SwaggerKindSchema)
-- Right (SwaggerItemsObject (Ref (Reference {getReference = "example"})))
--
-- >>> eitherDecode "[{\"$ref\":\"#/definitions/example\"}]" :: Either String (SwaggerItems 'SwaggerKindSchema)
-- Right (SwaggerItemsArray [Ref (Reference {getReference = "example"})])
--
instance FromJSON (SwaggerItems 'SwaggerKindSchema) where
  parseJSON :: Value -> Parser (SwaggerItems 'SwaggerKindSchema)
parseJSON js :: Value
js@(Object obj :: Object
obj)
      | Object -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Object
obj  = SwaggerItems 'SwaggerKindSchema
-> Parser (SwaggerItems 'SwaggerKindSchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SwaggerItems 'SwaggerKindSchema
 -> Parser (SwaggerItems 'SwaggerKindSchema))
-> SwaggerItems 'SwaggerKindSchema
-> Parser (SwaggerItems 'SwaggerKindSchema)
forall a b. (a -> b) -> a -> b
$ [Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsArray [] -- Nullary schema.
      | Bool
otherwise = Referenced Schema -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsObject (Referenced Schema -> SwaggerItems 'SwaggerKindSchema)
-> Parser (Referenced Schema)
-> Parser (SwaggerItems 'SwaggerKindSchema)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
  parseJSON js :: Value
js@(Array _)  = [Referenced Schema] -> SwaggerItems 'SwaggerKindSchema
SwaggerItemsArray  ([Referenced Schema] -> SwaggerItems 'SwaggerKindSchema)
-> Parser [Referenced Schema]
-> Parser (SwaggerItems 'SwaggerKindSchema)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Referenced Schema]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
  parseJSON _ = Parser (SwaggerItems 'SwaggerKindSchema)
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON Host where
  parseJSON :: Value -> Parser Host
parseJSON (String s :: Text
s) = case (Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
Text.unpack ([Text] -> [FilePath]) -> [Text] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> [Text]
Text.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ':') Text
s of
    [host :: FilePath
host] -> Host -> Parser Host
forall (m :: * -> *) a. Monad m => a -> m a
return (Host -> Parser Host) -> Host -> Parser Host
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe PortNumber -> Host
Host FilePath
host Maybe PortNumber
forall a. Maybe a
Nothing
    [host :: FilePath
host, port :: FilePath
port] -> case FilePath -> Maybe Integer
forall a. Read a => FilePath -> Maybe a
readMaybe FilePath
port of
      Nothing -> FilePath -> Parser Host
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser Host) -> FilePath -> Parser Host
forall a b. (a -> b) -> a -> b
$ "Invalid port `" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
port FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ "'"
      Just p :: Integer
p -> Host -> Parser Host
forall (m :: * -> *) a. Monad m => a -> m a
return (Host -> Parser Host) -> Host -> Parser Host
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe PortNumber -> Host
Host FilePath
host (PortNumber -> Maybe PortNumber
forall a. a -> Maybe a
Just (Integer -> PortNumber
forall a. Num a => Integer -> a
fromInteger Integer
p))
    _ -> FilePath -> Parser Host
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser Host) -> FilePath -> Parser Host
forall a b. (a -> b) -> a -> b
$ "Invalid host `" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> FilePath
Text.unpack Text
s FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ "'"
  parseJSON _ = Parser Host
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON MimeList where
  parseJSON :: Value -> Parser MimeList
parseJSON js :: Value
js = ([MediaType] -> MimeList
MimeList ([MediaType] -> MimeList)
-> ([FilePath] -> [MediaType]) -> [FilePath] -> MimeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> MediaType) -> [FilePath] -> [MediaType]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString) ([FilePath] -> MimeList) -> Parser [FilePath] -> Parser MimeList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [FilePath]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js

instance FromJSON Param where
  parseJSON :: Value -> Parser Param
parseJSON = Value -> Parser Param
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON ParamAnySchema where
  parseJSON :: Value -> Parser ParamAnySchema
parseJSON js :: Value
js@(Object o :: Object
o) = do
    (Text
i :: Text) <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "in"
    case Text
i of
      "body" -> do
        Value
schema <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: "schema"
        Referenced Schema -> ParamAnySchema
ParamBody (Referenced Schema -> ParamAnySchema)
-> Parser (Referenced Schema) -> Parser ParamAnySchema
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
schema
      _ -> ParamOtherSchema -> ParamAnySchema
ParamOther (ParamOtherSchema -> ParamAnySchema)
-> Parser ParamOtherSchema -> Parser ParamAnySchema
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ParamOtherSchema
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
  parseJSON _ = Parser ParamAnySchema
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON ParamOtherSchema where
  parseJSON :: Value -> Parser ParamOtherSchema
parseJSON = Value -> Parser ParamOtherSchema
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON Responses where
  parseJSON :: Value -> Parser Responses
parseJSON (Object o :: Object
o) = Maybe (Referenced Response)
-> InsOrdHashMap Int (Referenced Response) -> Responses
Responses
    (Maybe (Referenced Response)
 -> InsOrdHashMap Int (Referenced Response) -> Responses)
-> Parser (Maybe (Referenced Response))
-> Parser (InsOrdHashMap Int (Referenced Response) -> Responses)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe (Referenced Response))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? "default"
    Parser (InsOrdHashMap Int (Referenced Response) -> Responses)
-> Parser (InsOrdHashMap Int (Referenced Response))
-> Parser Responses
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser (InsOrdHashMap Int (Referenced Response))
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object (Key -> Object -> Object
forall v. Key -> KeyMap v -> KeyMap v
KM.delete "default" Object
o))
  parseJSON _ = Parser Responses
forall (f :: * -> *) a. Alternative f => f a
empty

instance FromJSON Example where
  parseJSON :: Value -> Parser Example
parseJSON js :: Value
js = do
    Map FilePath Value
m <- Value -> Parser (Map FilePath Value)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
    Example -> Parser Example
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Example -> Parser Example) -> Example -> Parser Example
forall a b. (a -> b) -> a -> b
$ Map MediaType Value -> Example
Example ((FilePath -> MediaType)
-> Map FilePath Value -> Map MediaType Value
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString Map FilePath Value
m)

instance FromJSON Response where
  parseJSON :: Value -> Parser Response
parseJSON = Value -> Parser Response
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON Operation where
  parseJSON :: Value -> Parser Operation
parseJSON = Value -> Parser Operation
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON PathItem where
  parseJSON :: Value -> Parser PathItem
parseJSON = Value -> Parser PathItem
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON SecurityDefinitions where
  parseJSON :: Value -> Parser SecurityDefinitions
parseJSON js :: Value
js = Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions (Definitions SecurityScheme -> SecurityDefinitions)
-> Parser (Definitions SecurityScheme)
-> Parser SecurityDefinitions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Definitions SecurityScheme)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js

instance FromJSON Reference where
  parseJSON :: Value -> Parser Reference
parseJSON (Object o :: Object
o) = Text -> Reference
Reference (Text -> Reference) -> Parser Text -> Parser Reference
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: "$ref"
  parseJSON _ = Parser Reference
forall (f :: * -> *) a. Alternative f => f a
empty

referencedParseJSON :: FromJSON a => Text -> Value -> JSON.Parser (Referenced a)
referencedParseJSON :: Text -> Value -> Parser (Referenced a)
referencedParseJSON prefix :: Text
prefix js :: Value
js@(Object o :: Object
o) = do
  Maybe Text
ms <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? "$ref"
  case Maybe Text
ms of
    Nothing -> a -> Referenced a
forall a. a -> Referenced a
Inline (a -> Referenced a) -> Parser a -> Parser (Referenced a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
    Just s :: Text
s  -> Reference -> Referenced a
forall a. Reference -> Referenced a
Ref (Reference -> Referenced a)
-> Parser Reference -> Parser (Referenced a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Reference
parseRef Text
s
  where
    parseRef :: Text -> Parser Reference
parseRef s :: Text
s = do
      case Text -> Text -> Maybe Text
Text.stripPrefix Text
prefix Text
s of
        Nothing     -> FilePath -> Parser Reference
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser Reference) -> FilePath -> Parser Reference
forall a b. (a -> b) -> a -> b
$ "expected $ref of the form \"" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
Text.unpack Text
prefix FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> "*\", but got " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
forall a. Show a => a -> FilePath
show Text
s
        Just suffix :: Text
suffix -> Reference -> Parser Reference
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Reference
Reference Text
suffix)
referencedParseJSON _ _ = FilePath -> Parser (Referenced a)
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail "referenceParseJSON: not an object"

instance FromJSON (Referenced Schema)   where parseJSON :: Value -> Parser (Referenced Schema)
parseJSON = Text -> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON "#/definitions/"
instance FromJSON (Referenced Param)    where parseJSON :: Value -> Parser (Referenced Param)
parseJSON = Text -> Value -> Parser (Referenced Param)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON "#/parameters/"
instance FromJSON (Referenced Response) where parseJSON :: Value -> Parser (Referenced Response)
parseJSON = Text -> Value -> Parser (Referenced Response)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON "#/responses/"

instance FromJSON Xml where
  parseJSON :: Value -> Parser Xml
parseJSON = Options -> Value -> Parser Xml
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix "xml")

instance FromJSON (SwaggerType 'SwaggerKindSchema) where
  parseJSON :: Value -> Parser (SwaggerType 'SwaggerKindSchema)
parseJSON = [SwaggerType 'SwaggerKindSchema]
-> Value -> Parser (SwaggerType 'SwaggerKindSchema)
forall a. ToJSON a => [a] -> Value -> Parser a
parseOneOf [SwaggerType 'SwaggerKindSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerString, SwaggerType 'SwaggerKindSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerInteger, SwaggerType 'SwaggerKindSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerNumber, SwaggerType 'SwaggerKindSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerBoolean, SwaggerType 'SwaggerKindSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerArray, SwaggerType 'SwaggerKindSchema
SwaggerNull, SwaggerType 'SwaggerKindSchema
SwaggerObject]

instance FromJSON (SwaggerType 'SwaggerKindParamOtherSchema) where
  parseJSON :: Value -> Parser (SwaggerType 'SwaggerKindParamOtherSchema)
parseJSON = [SwaggerType 'SwaggerKindParamOtherSchema]
-> Value -> Parser (SwaggerType 'SwaggerKindParamOtherSchema)
forall a. ToJSON a => [a] -> Value -> Parser a
parseOneOf [SwaggerType 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerString, SwaggerType 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerInteger, SwaggerType 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerNumber, SwaggerType 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerBoolean, SwaggerType 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). SwaggerType t
SwaggerArray, SwaggerType 'SwaggerKindParamOtherSchema
SwaggerFile]

instance FromJSON (SwaggerType ('SwaggerKindNormal t)) where
  parseJSON :: Value -> Parser (SwaggerType ('SwaggerKindNormal t))
parseJSON = [SwaggerType ('SwaggerKindNormal t)]
-> Value -> Parser (SwaggerType ('SwaggerKindNormal t))
forall a. ToJSON a => [a] -> Value -> Parser a
parseOneOf [SwaggerType ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). SwaggerType t
SwaggerString, SwaggerType ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). SwaggerType t
SwaggerInteger, SwaggerType ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). SwaggerType t
SwaggerNumber, SwaggerType ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). SwaggerType t
SwaggerBoolean, SwaggerType ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). SwaggerType t
SwaggerArray]

instance FromJSON (CollectionFormat ('SwaggerKindNormal t)) where
  parseJSON :: Value -> Parser (CollectionFormat ('SwaggerKindNormal t))
parseJSON = [CollectionFormat ('SwaggerKindNormal t)]
-> Value -> Parser (CollectionFormat ('SwaggerKindNormal t))
forall a. ToJSON a => [a] -> Value -> Parser a
parseOneOf [CollectionFormat ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). CollectionFormat t
CollectionCSV, CollectionFormat ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). CollectionFormat t
CollectionSSV, CollectionFormat ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). CollectionFormat t
CollectionTSV, CollectionFormat ('SwaggerKindNormal t)
forall (t :: SwaggerKind *). CollectionFormat t
CollectionPipes]

-- NOTE: There aren't collections of 'Schema'
--instance FromJSON (CollectionFormat (SwaggerKindSchema)) where
--  parseJSON = parseOneOf [CollectionCSV, CollectionSSV, CollectionTSV, CollectionPipes]

instance FromJSON (CollectionFormat 'SwaggerKindParamOtherSchema) where
  parseJSON :: Value -> Parser (CollectionFormat 'SwaggerKindParamOtherSchema)
parseJSON = [CollectionFormat 'SwaggerKindParamOtherSchema]
-> Value -> Parser (CollectionFormat 'SwaggerKindParamOtherSchema)
forall a. ToJSON a => [a] -> Value -> Parser a
parseOneOf [CollectionFormat 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). CollectionFormat t
CollectionCSV, CollectionFormat 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). CollectionFormat t
CollectionSSV, CollectionFormat 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). CollectionFormat t
CollectionTSV, CollectionFormat 'SwaggerKindParamOtherSchema
forall (t :: SwaggerKind *). CollectionFormat t
CollectionPipes, CollectionFormat 'SwaggerKindParamOtherSchema
CollectionMulti]

instance (FromJSON (SwaggerType ('SwaggerKindNormal t)), FromJSON (SwaggerItems ('SwaggerKindNormal t))) => FromJSON (ParamSchema ('SwaggerKindNormal t)) where
  parseJSON :: Value -> Parser (ParamSchema ('SwaggerKindNormal t))
parseJSON = Value -> Parser (ParamSchema ('SwaggerKindNormal t))
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON (ParamSchema 'SwaggerKindParamOtherSchema) where
  parseJSON :: Value -> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
parseJSON = Value -> Parser (ParamSchema 'SwaggerKindParamOtherSchema)
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON (ParamSchema 'SwaggerKindSchema) where
  parseJSON :: Value -> Parser (ParamSchema 'SwaggerKindSchema)
parseJSON = Value -> Parser (ParamSchema 'SwaggerKindSchema)
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

instance FromJSON AdditionalProperties where
  parseJSON :: Value -> Parser AdditionalProperties
parseJSON (Bool b :: Bool
b) = AdditionalProperties -> Parser AdditionalProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AdditionalProperties -> Parser AdditionalProperties)
-> AdditionalProperties -> Parser AdditionalProperties
forall a b. (a -> b) -> a -> b
$ Bool -> AdditionalProperties
AdditionalPropertiesAllowed Bool
b
  parseJSON js :: Value
js = Referenced Schema -> AdditionalProperties
AdditionalPropertiesSchema (Referenced Schema -> AdditionalProperties)
-> Parser (Referenced Schema) -> Parser AdditionalProperties
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js

instance HasSwaggerAesonOptions Header where
  swaggerAesonOptions :: Proxy Header -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "header" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "paramSchema"
instance HasSwaggerAesonOptions OAuth2Params where
  swaggerAesonOptions :: Proxy OAuth2Params -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "oauth2" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "flow"
instance HasSwaggerAesonOptions Operation where
  swaggerAesonOptions :: Proxy Operation -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "operation"
instance HasSwaggerAesonOptions Param where
  swaggerAesonOptions :: Proxy Param -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "param" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "schema"
instance HasSwaggerAesonOptions ParamOtherSchema where
  swaggerAesonOptions :: Proxy ParamOtherSchema -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "paramOtherSchema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "paramSchema"
instance HasSwaggerAesonOptions PathItem where
  swaggerAesonOptions :: Proxy PathItem -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "pathItem"
instance HasSwaggerAesonOptions Response where
  swaggerAesonOptions :: Proxy Response -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "response"
instance HasSwaggerAesonOptions Responses where
  swaggerAesonOptions :: Proxy Responses -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "responses" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "responses"
instance HasSwaggerAesonOptions SecurityScheme where
  swaggerAesonOptions :: Proxy SecurityScheme -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "securityScheme" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "type"
instance HasSwaggerAesonOptions Schema where
  swaggerAesonOptions :: Proxy Schema -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "schema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "paramSchema"
instance HasSwaggerAesonOptions Swagger where
  swaggerAesonOptions :: Proxy Swagger -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "swagger" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& ([(Text, Value)] -> Identity [(Text, Value)])
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions [(Text, Value)]
saoAdditionalPairs (([(Text, Value)] -> Identity [(Text, Value)])
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> [(Text, Value)] -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [("swagger", "2.0")]

instance HasSwaggerAesonOptions (ParamSchema ('SwaggerKindNormal t)) where
  swaggerAesonOptions :: Proxy (ParamSchema ('SwaggerKindNormal t)) -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "paramSchema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "items"
instance HasSwaggerAesonOptions (ParamSchema 'SwaggerKindParamOtherSchema) where
  swaggerAesonOptions :: Proxy (ParamSchema 'SwaggerKindParamOtherSchema)
-> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "paramSchema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ "items"
-- NOTE: Schema doesn't have 'items' sub object!
instance HasSwaggerAesonOptions (ParamSchema 'SwaggerKindSchema) where
  swaggerAesonOptions :: Proxy (ParamSchema 'SwaggerKindSchema) -> SwaggerAesonOptions
swaggerAesonOptions _ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions "paramSchema"

instance AesonDefaultValue (ParamSchema s)
instance AesonDefaultValue OAuth2Flow
instance AesonDefaultValue Responses
instance AesonDefaultValue ParamAnySchema
instance AesonDefaultValue SecuritySchemeType
instance AesonDefaultValue (SwaggerType a)
instance AesonDefaultValue MimeList where defaultValue :: Maybe MimeList
defaultValue = MimeList -> Maybe MimeList
forall a. a -> Maybe a
Just MimeList
forall a. Monoid a => a
mempty
instance AesonDefaultValue Info
instance AesonDefaultValue ParamLocation
instance AesonDefaultValue SecurityDefinitions where defaultValue :: Maybe SecurityDefinitions
defaultValue = SecurityDefinitions -> Maybe SecurityDefinitions
forall a. a -> Maybe a
Just (SecurityDefinitions -> Maybe SecurityDefinitions)
-> SecurityDefinitions -> Maybe SecurityDefinitions
forall a b. (a -> b) -> a -> b
$ Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions Definitions SecurityScheme
forall a. Monoid a => a
mempty