{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# 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.OpenApi.Internal where

import Prelude ()
import Prelude.Compat

import           Control.Applicative
import           Control.Lens          ((&), (.~), (?~))
import           Data.Aeson            hiding (Encoding)
import qualified Data.Aeson.Types      as JSON
import           Data.Data             (Constr, Data (..), DataType, Fixity (..), Typeable,
                                        constrIndex, mkConstr, mkDataType)
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.Scientific       (Scientific)
import           Data.Semigroup.Compat (Semigroup (..))
import           Data.String           (IsString (..))
import           Data.Text             (Text)
import qualified Data.Text             as Text
import           Data.Text.Encoding    (encodeUtf8)
import           GHC.Generics          (Generic)
import           Network.HTTP.Media    (MediaType, mainType, parameters, parseAccept, subType, (//),
                                        (/:))
import           Network.Socket        (HostName, PortNumber)
import           Text.Read             (readMaybe)

import           Data.HashMap.Strict.InsOrd (InsOrdHashMap)
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap

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

-- $setup
-- >>> :seti -XDataKinds
-- >>> import Data.Aeson
-- >>> import Data.ByteString.Lazy.Char8 as BSL
-- >>> import Data.OpenApi.Internal.Utils

-- | 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 OpenApi = OpenApi
  { -- | Provides metadata about the API.
    -- The metadata can be used by the clients if needed.
    OpenApi -> Info
_openApiInfo :: Info

    -- | An array of Server Objects, which provide connectivity information
    -- to a target server. If the servers property is not provided, or is an empty array,
    -- the default value would be a 'Server' object with a url value of @/@.
  , OpenApi -> [Server]
_openApiServers :: [Server]

    -- | The available paths and operations for the API.
  , OpenApi -> InsOrdHashMap FilePath PathItem
_openApiPaths :: InsOrdHashMap FilePath PathItem

    -- | An element to hold various schemas for the specification.
  , OpenApi -> Components
_openApiComponents :: Components

    -- | A declaration of which security mechanisms can be used across the API.
    -- The list of values includes alternative security requirement objects that can be used.
    -- Only one of the security requirement objects need to be satisfied to authorize a request.
    -- Individual operations can override this definition.
    -- To make security optional, an empty security requirement can be included in the array.
  , OpenApi -> [SecurityRequirement]
_openApiSecurity :: [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.
  , OpenApi -> InsOrdHashSet Tag
_openApiTags :: InsOrdHashSet Tag

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

-- | The object provides metadata about the API.
-- The metadata MAY be used by the clients if needed,
-- and MAY be presented in editing or documentation generation tools for convenience.
data Info = Info
  { -- | The title of the API.
    Info -> Text
_infoTitle :: Text

    -- | A short description of the API.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY be used for rich text representation.
  , Info -> Maybe Text
_infoDescription :: Maybe Text

    -- | A URL to the Terms of Service for the API. MUST be in the format of a URL.
  , 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

    -- | The version of the OpenAPI document (which is distinct from the
    -- OpenAPI Specification version or the API implementation 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 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

-- | An object representing a Server.
data Server = Server
  { -- | A URL to the target host. This URL supports Server Variables and MAY be relative,
    -- to indicate that the host location is relative to the location where
    -- the OpenAPI document is being served. Variable substitutions will be made when
    -- a variable is named in @{brackets}@.
    Server -> Text
_serverUrl :: Text

    -- | An optional string describing the host designated by the URL.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY be used for rich text representation.
  , Server -> Maybe Text
_serverDescription :: Maybe Text

    -- | A map between a variable name and its value.
    -- The value is used for substitution in the server's URL template.
  , Server -> InsOrdHashMap Text ServerVariable
_serverVariables :: InsOrdHashMap Text ServerVariable
  } deriving (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c== :: Server -> Server -> Bool
Eq, Int -> Server -> ShowS
[Server] -> ShowS
Server -> FilePath
(Int -> Server -> ShowS)
-> (Server -> FilePath) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Server] -> ShowS
$cshowList :: [Server] -> ShowS
show :: Server -> FilePath
$cshow :: Server -> FilePath
showsPrec :: Int -> Server -> ShowS
$cshowsPrec :: Int -> Server -> ShowS
Show, (forall x. Server -> Rep Server x)
-> (forall x. Rep Server x -> Server) -> Generic Server
forall x. Rep Server x -> Server
forall x. Server -> Rep Server x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Server x -> Server
$cfrom :: forall x. Server -> Rep Server x
Generic, Typeable Server
DataType
Constr
Typeable Server
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Server -> c Server)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Server)
-> (Server -> Constr)
-> (Server -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Server))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server))
-> ((forall b. Data b => b -> b) -> Server -> Server)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Server -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Server -> r)
-> (forall u. (forall d. Data d => d -> u) -> Server -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Server -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Server -> m Server)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Server -> m Server)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Server -> m Server)
-> Data Server
Server -> DataType
Server -> Constr
(forall b. Data b => b -> b) -> Server -> Server
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
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) -> Server -> u
forall u. (forall d. Data d => d -> u) -> Server -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Server -> m Server
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Server)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server)
$cServer :: Constr
$tServer :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Server -> m Server
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server
gmapMp :: (forall d. Data d => d -> m d) -> Server -> m Server
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server
gmapM :: (forall d. Data d => d -> m d) -> Server -> m Server
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Server -> m Server
gmapQi :: Int -> (forall d. Data d => d -> u) -> Server -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Server -> u
gmapQ :: (forall d. Data d => d -> u) -> Server -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Server -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
gmapT :: (forall b. Data b => b -> b) -> Server -> Server
$cgmapT :: (forall b. Data b => b -> b) -> Server -> Server
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Server)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Server)
dataTypeOf :: Server -> DataType
$cdataTypeOf :: Server -> DataType
toConstr :: Server -> Constr
$ctoConstr :: Server -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
$cp1Data :: Typeable Server
Data, Typeable)

data ServerVariable = ServerVariable
  { -- | An enumeration of string values to be used if the substitution options
    -- are from a limited set. The array SHOULD NOT be empty.
    ServerVariable -> Maybe (InsOrdHashSet Text)
_serverVariableEnum :: Maybe (InsOrdHashSet Text) -- TODO NonEmpty

    -- | The default value to use for substitution, which SHALL be sent if an alternate value
    -- is not supplied. Note this behavior is different than the 'Schema\ Object's treatment
    -- of default values, because in those cases parameter values are optional.
    -- If the '_serverVariableEnum' is defined, the value SHOULD exist in the enum's values.
  , ServerVariable -> Text
_serverVariableDefault :: Text

    -- | An optional description for the server variable.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY be used for rich text representation.
  , ServerVariable -> Maybe Text
_serverVariableDescription :: Maybe Text
  } deriving (ServerVariable -> ServerVariable -> Bool
(ServerVariable -> ServerVariable -> Bool)
-> (ServerVariable -> ServerVariable -> Bool) -> Eq ServerVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerVariable -> ServerVariable -> Bool
$c/= :: ServerVariable -> ServerVariable -> Bool
== :: ServerVariable -> ServerVariable -> Bool
$c== :: ServerVariable -> ServerVariable -> Bool
Eq, Int -> ServerVariable -> ShowS
[ServerVariable] -> ShowS
ServerVariable -> FilePath
(Int -> ServerVariable -> ShowS)
-> (ServerVariable -> FilePath)
-> ([ServerVariable] -> ShowS)
-> Show ServerVariable
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ServerVariable] -> ShowS
$cshowList :: [ServerVariable] -> ShowS
show :: ServerVariable -> FilePath
$cshow :: ServerVariable -> FilePath
showsPrec :: Int -> ServerVariable -> ShowS
$cshowsPrec :: Int -> ServerVariable -> ShowS
Show, (forall x. ServerVariable -> Rep ServerVariable x)
-> (forall x. Rep ServerVariable x -> ServerVariable)
-> Generic ServerVariable
forall x. Rep ServerVariable x -> ServerVariable
forall x. ServerVariable -> Rep ServerVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ServerVariable x -> ServerVariable
$cfrom :: forall x. ServerVariable -> Rep ServerVariable x
Generic, Typeable ServerVariable
DataType
Constr
Typeable ServerVariable
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ServerVariable -> c ServerVariable)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ServerVariable)
-> (ServerVariable -> Constr)
-> (ServerVariable -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ServerVariable))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ServerVariable))
-> ((forall b. Data b => b -> b)
    -> ServerVariable -> ServerVariable)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ServerVariable -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ServerVariable -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ServerVariable -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ServerVariable -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ServerVariable -> m ServerVariable)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ServerVariable -> m ServerVariable)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ServerVariable -> m ServerVariable)
-> Data ServerVariable
ServerVariable -> DataType
ServerVariable -> Constr
(forall b. Data b => b -> b) -> ServerVariable -> ServerVariable
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
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) -> ServerVariable -> u
forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ServerVariable)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable)
$cServerVariable :: Constr
$tServerVariable :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
gmapMp :: (forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
gmapM :: (forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
gmapQi :: Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
gmapQ :: (forall d. Data d => d -> u) -> ServerVariable -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
gmapT :: (forall b. Data b => b -> b) -> ServerVariable -> ServerVariable
$cgmapT :: (forall b. Data b => b -> b) -> ServerVariable -> ServerVariable
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ServerVariable)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ServerVariable)
dataTypeOf :: ServerVariable -> DataType
$cdataTypeOf :: ServerVariable -> DataType
toConstr :: ServerVariable -> Constr
$ctoConstr :: ServerVariable -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
$cp1Data :: Typeable ServerVariable
Data, Typeable)

instance IsString Server where
  fromString :: FilePath -> Server
fromString FilePath
s = Text -> Maybe Text -> InsOrdHashMap Text ServerVariable -> Server
Server (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe Text
forall a. Maybe a
Nothing InsOrdHashMap Text ServerVariable
forall a. Monoid a => a
mempty

-- | Holds a set of reusable objects for different aspects of the OAS.
-- All objects defined within the components object will have no effect on the API
-- unless they are explicitly referenced from properties outside the components object.
data Components = Components
  { Components -> Definitions Schema
_componentsSchemas :: Definitions Schema
  , Components -> Definitions Response
_componentsResponses :: Definitions Response
  , Components -> Definitions Param
_componentsParameters :: Definitions Param
  , Components -> Definitions Example
_componentsExamples :: Definitions Example
  , Components -> Definitions RequestBody
_componentsRequestBodies :: Definitions RequestBody
  , Components -> Definitions Header
_componentsHeaders :: Definitions Header
  , Components -> Definitions SecurityScheme
_componentsSecuritySchemes :: Definitions SecurityScheme
  , Components -> Definitions Link
_componentsLinks :: Definitions Link
  , Components -> Definitions Callback
_componentsCallbacks :: Definitions Callback
  } deriving (Components -> Components -> Bool
(Components -> Components -> Bool)
-> (Components -> Components -> Bool) -> Eq Components
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Components -> Components -> Bool
$c/= :: Components -> Components -> Bool
== :: Components -> Components -> Bool
$c== :: Components -> Components -> Bool
Eq, Int -> Components -> ShowS
[Components] -> ShowS
Components -> FilePath
(Int -> Components -> ShowS)
-> (Components -> FilePath)
-> ([Components] -> ShowS)
-> Show Components
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Components] -> ShowS
$cshowList :: [Components] -> ShowS
show :: Components -> FilePath
$cshow :: Components -> FilePath
showsPrec :: Int -> Components -> ShowS
$cshowsPrec :: Int -> Components -> ShowS
Show, (forall x. Components -> Rep Components x)
-> (forall x. Rep Components x -> Components) -> Generic Components
forall x. Rep Components x -> Components
forall x. Components -> Rep Components x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Components x -> Components
$cfrom :: forall x. Components -> Rep Components x
Generic, Typeable Components
DataType
Constr
Typeable Components
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Components -> c Components)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Components)
-> (Components -> Constr)
-> (Components -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Components))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Components))
-> ((forall b. Data b => b -> b) -> Components -> Components)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Components -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Components -> r)
-> (forall u. (forall d. Data d => d -> u) -> Components -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Components -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Components -> m Components)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Components -> m Components)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Components -> m Components)
-> Data Components
Components -> DataType
Components -> Constr
(forall b. Data b => b -> b) -> Components -> Components
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
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) -> Components -> u
forall u. (forall d. Data d => d -> u) -> Components -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Components -> m Components
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Components)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Components)
$cComponents :: Constr
$tComponents :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Components -> m Components
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components
gmapMp :: (forall d. Data d => d -> m d) -> Components -> m Components
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components
gmapM :: (forall d. Data d => d -> m d) -> Components -> m Components
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Components -> m Components
gmapQi :: Int -> (forall d. Data d => d -> u) -> Components -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Components -> u
gmapQ :: (forall d. Data d => d -> u) -> Components -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Components -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
gmapT :: (forall b. Data b => b -> b) -> Components -> Components
$cgmapT :: (forall b. Data b => b -> b) -> Components -> Components
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Components)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Components)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Components)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Components)
dataTypeOf :: Components -> DataType
$cdataTypeOf :: Components -> DataType
toConstr :: Components -> Constr
$ctoConstr :: Components -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
$cp1Data :: Typeable Components
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
  { -- | An optional, string summary, intended to apply to all operations in this path.
    PathItem -> Maybe Text
_pathItemSummary :: Maybe Text

    -- | An optional, string description, intended to apply to all operations in this path.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY be used for rich text representation.
  , PathItem -> Maybe Text
_pathItemDescription :: Maybe Text

    -- | 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 definition of a TRACE operation on this path.
  , PathItem -> Maybe Operation
_pathItemTrace :: Maybe Operation

    -- | An alternative server array to service all operations in this path.
  , PathItem -> [Server]
_pathItemServers :: [Server]

    -- | 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.
    -- [CommonMark syntax](https://spec.commonmark.org/) 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.
    -- The operationId value is **case-sensitive**.
    -- Tools and libraries MAY use the operationId to uniquely identify an operation, therefore,
    -- it is RECOMMENDED to follow common programming naming conventions.
  , Operation -> Maybe Text
_operationOperationId :: Maybe Text

    -- | 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 request body applicable for this operation.
    -- The requestBody is only supported in HTTP methods where the HTTP 1.1
    -- specification [RFC7231](https://tools.ietf.org/html/rfc7231#section-4.3.1)
    -- has explicitly defined semantics for request bodies.
    -- In other cases where the HTTP spec is vague, requestBody SHALL be ignored by consumers.
  , Operation -> Maybe (Referenced RequestBody)
_operationRequestBody :: Maybe (Referenced RequestBody)

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

    -- | A map of possible out-of band callbacks related to the parent operation.
    -- The key is a unique identifier for the 'Callback' Object.
    -- Each value in the map is a 'Callback' Object that describes a request
    -- that may be initiated by the API provider and the expected responses.
  , Operation -> InsOrdHashMap Text (Referenced Callback)
_operationCallbacks :: InsOrdHashMap Text (Referenced Callback)

    -- | 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]

    -- | An alternative server array to service this operation.
    -- If an alternative server object is specified at the 'PathItem' Object or Root level,
    -- it will be overridden by this value.
  , Operation -> [Server]
_operationServers :: [Server]
  } 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)

-- This instance should be in @http-media@.
instance Data MediaType where
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaType
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
    Int
1 -> c (Map ByteString ByteString -> MediaType) -> c MediaType
forall b r. Data b => c (b -> r) -> c r
k (c (ByteString -> Map ByteString ByteString -> MediaType)
-> c (Map ByteString ByteString -> MediaType)
forall b r. Data b => c (b -> r) -> c r
k (c (ByteString
   -> ByteString -> Map ByteString ByteString -> MediaType)
-> c (ByteString -> Map ByteString ByteString -> MediaType)
forall b r. Data b => c (b -> r) -> c r
k ((ByteString
 -> ByteString -> Map ByteString ByteString -> MediaType)
-> c (ByteString
      -> ByteString -> Map ByteString ByteString -> MediaType)
forall r. r -> c r
z (\ByteString
main ByteString
sub Map ByteString ByteString
params -> (MediaType -> (ByteString, ByteString) -> MediaType)
-> MediaType -> [(ByteString, ByteString)] -> MediaType
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl MediaType -> (ByteString, ByteString) -> MediaType
(/:) (ByteString
main ByteString -> ByteString -> MediaType
// ByteString
sub) (Map ByteString ByteString -> [(ByteString, ByteString)]
forall k a. Map k a -> [(k, a)]
Map.toList Map ByteString ByteString
params)))))
    Int
_ -> FilePath -> c MediaType
forall a. HasCallStack => FilePath -> a
error (FilePath -> c MediaType) -> FilePath -> c MediaType
forall a b. (a -> b) -> a -> b
$ FilePath
"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]
++ FilePath
" is not of type MediaType."

  toConstr :: MediaType -> Constr
toConstr MediaType
_ = Constr
mediaTypeConstr

  dataTypeOf :: MediaType -> DataType
dataTypeOf MediaType
_ = DataType
mediaTypeData

mediaTypeConstr :: Constr
mediaTypeConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
mediaTypeData FilePath
"MediaType" [] Fixity
Prefix
mediaTypeData :: DataType
mediaTypeData = FilePath -> [Constr] -> DataType
mkDataType FilePath
"MediaType" [Constr
mediaTypeConstr]

instance Hashable MediaType where
  hashWithSalt :: Int -> MediaType -> Int
hashWithSalt Int
salt MediaType
mt = Int
salt Int -> FilePath -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` MediaType -> FilePath
forall a. Show a => a -> FilePath
show MediaType
mt

-- | Describes a single request body.
data RequestBody = RequestBody
  { -- | A brief description of the request body. This could contain examples of use.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY be used for rich text representation.
    RequestBody -> Maybe Text
_requestBodyDescription :: Maybe Text

    -- | The content of the request body.
    -- The key is a media type or media type range and the value describes it.
    -- For requests that match multiple keys, only the most specific key is applicable.
    -- e.g. @text/plain@ overrides @text/*@
  , RequestBody -> InsOrdHashMap MediaType MediaTypeObject
_requestBodyContent :: InsOrdHashMap MediaType MediaTypeObject

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

-- | Each Media Type Object provides schema and examples for the media type identified by its key.
data MediaTypeObject = MediaTypeObject
  { MediaTypeObject -> Maybe (Referenced Schema)
_mediaTypeObjectSchema :: Maybe (Referenced Schema)

    -- | Example of the media type.
    -- The example object SHOULD be in the correct format as specified by the media type.
  , MediaTypeObject -> Maybe Value
_mediaTypeObjectExample :: Maybe Value

    -- | Examples of the media type.
    -- Each example object SHOULD match the media type and specified schema if present.
  , MediaTypeObject -> InsOrdHashMap Text (Referenced Example)
_mediaTypeObjectExamples :: InsOrdHashMap Text (Referenced Example)

    -- | A map between a property name and its encoding information.
    -- The key, being the property name, MUST exist in the schema as a property.
    -- The encoding object SHALL only apply to 'RequestBody' objects when the media type
    -- is @multipart@ or @application/x-www-form-urlencoded@.
  , MediaTypeObject -> InsOrdHashMap Text Encoding
_mediaTypeObjectEncoding :: InsOrdHashMap Text Encoding
  } deriving (MediaTypeObject -> MediaTypeObject -> Bool
(MediaTypeObject -> MediaTypeObject -> Bool)
-> (MediaTypeObject -> MediaTypeObject -> Bool)
-> Eq MediaTypeObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaTypeObject -> MediaTypeObject -> Bool
$c/= :: MediaTypeObject -> MediaTypeObject -> Bool
== :: MediaTypeObject -> MediaTypeObject -> Bool
$c== :: MediaTypeObject -> MediaTypeObject -> Bool
Eq, Int -> MediaTypeObject -> ShowS
[MediaTypeObject] -> ShowS
MediaTypeObject -> FilePath
(Int -> MediaTypeObject -> ShowS)
-> (MediaTypeObject -> FilePath)
-> ([MediaTypeObject] -> ShowS)
-> Show MediaTypeObject
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MediaTypeObject] -> ShowS
$cshowList :: [MediaTypeObject] -> ShowS
show :: MediaTypeObject -> FilePath
$cshow :: MediaTypeObject -> FilePath
showsPrec :: Int -> MediaTypeObject -> ShowS
$cshowsPrec :: Int -> MediaTypeObject -> ShowS
Show, (forall x. MediaTypeObject -> Rep MediaTypeObject x)
-> (forall x. Rep MediaTypeObject x -> MediaTypeObject)
-> Generic MediaTypeObject
forall x. Rep MediaTypeObject x -> MediaTypeObject
forall x. MediaTypeObject -> Rep MediaTypeObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MediaTypeObject x -> MediaTypeObject
$cfrom :: forall x. MediaTypeObject -> Rep MediaTypeObject x
Generic, Typeable MediaTypeObject
DataType
Constr
Typeable MediaTypeObject
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c MediaTypeObject)
-> (MediaTypeObject -> Constr)
-> (MediaTypeObject -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c MediaTypeObject))
-> ((forall b. Data b => b -> b)
    -> MediaTypeObject -> MediaTypeObject)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> MediaTypeObject -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> MediaTypeObject -> m MediaTypeObject)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> MediaTypeObject -> m MediaTypeObject)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> MediaTypeObject -> m MediaTypeObject)
-> Data MediaTypeObject
MediaTypeObject -> DataType
MediaTypeObject -> Constr
(forall b. Data b => b -> b) -> MediaTypeObject -> MediaTypeObject
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
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) -> MediaTypeObject -> u
forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject)
$cMediaTypeObject :: Constr
$tMediaTypeObject :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
gmapMp :: (forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
gmapM :: (forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
gmapQ :: (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
gmapT :: (forall b. Data b => b -> b) -> MediaTypeObject -> MediaTypeObject
$cgmapT :: (forall b. Data b => b -> b) -> MediaTypeObject -> MediaTypeObject
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject)
dataTypeOf :: MediaTypeObject -> DataType
$cdataTypeOf :: MediaTypeObject -> DataType
toConstr :: MediaTypeObject -> Constr
$ctoConstr :: MediaTypeObject -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
$cp1Data :: Typeable MediaTypeObject
Data, Typeable)

-- | In order to support common ways of serializing simple parameters, a set of style values are defined.
data Style
  = StyleMatrix
    -- ^ Path-style parameters defined by [RFC6570](https://tools.ietf.org/html/rfc6570#section-3.2.7).
  | StyleLabel
    -- ^ Label style parameters defined by [RFC6570](https://tools.ietf.org/html/rfc6570#section-3.2.7).
  | StyleForm
    -- ^ Form style parameters defined by [RFC6570](https://tools.ietf.org/html/rfc6570#section-3.2.7).
    -- This option replaces @collectionFormat@ with a @csv@ (when @explode@ is false) or @multi@
    -- (when explode is true) value from OpenAPI 2.0.
  | StyleSimple
    -- ^ Simple style parameters defined by [RFC6570](https://tools.ietf.org/html/rfc6570#section-3.2.7).
    -- This option replaces @collectionFormat@ with a @csv@ value from OpenAPI 2.0.
  | StyleSpaceDelimited
    -- ^ Space separated array values.
    -- This option replaces @collectionFormat@ equal to @ssv@ from OpenAPI 2.0.
  | StylePipeDelimited
    -- ^ Pipe separated array values.
    -- This option replaces @collectionFormat@ equal to @pipes@ from OpenAPI 2.0.
  | StyleDeepObject
    -- ^ Provides a simple way of rendering nested objects using form parameters.
  deriving (Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, Int -> Style -> ShowS
[Style] -> ShowS
Style -> FilePath
(Int -> Style -> ShowS)
-> (Style -> FilePath) -> ([Style] -> ShowS) -> Show Style
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> FilePath
$cshow :: Style -> FilePath
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show, (forall x. Style -> Rep Style x)
-> (forall x. Rep Style x -> Style) -> Generic Style
forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Style x -> Style
$cfrom :: forall x. Style -> Rep Style x
Generic, Typeable Style
DataType
Constr
Typeable Style
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Style -> c Style)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Style)
-> (Style -> Constr)
-> (Style -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Style))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style))
-> ((forall b. Data b => b -> b) -> Style -> Style)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall u. (forall d. Data d => d -> u) -> Style -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Style -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> Data Style
Style -> DataType
Style -> Constr
(forall b. Data b => b -> b) -> Style -> Style
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
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) -> Style -> u
forall u. (forall d. Data d => d -> u) -> Style -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cStyleDeepObject :: Constr
$cStylePipeDelimited :: Constr
$cStyleSpaceDelimited :: Constr
$cStyleSimple :: Constr
$cStyleForm :: Constr
$cStyleLabel :: Constr
$cStyleMatrix :: Constr
$tStyle :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapMp :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapM :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQ :: (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapT :: (forall b. Data b => b -> b) -> Style -> Style
$cgmapT :: (forall b. Data b => b -> b) -> Style -> Style
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Style)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
dataTypeOf :: Style -> DataType
$cdataTypeOf :: Style -> DataType
toConstr :: Style -> Constr
$ctoConstr :: Style -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cp1Data :: Typeable Style
Data, Typeable)

data Encoding = Encoding
  { -- | The Content-Type for encoding a specific property.
    -- Default value depends on the property type: for @string@
    -- with format being @binary@ – @application/octet-stream@;
    -- for other primitive types – @text/plain@; for object - @application/json@;
    -- for array – the default is defined based on the inner type.
    -- The value can be a specific media type (e.g. @application/json@),
    -- a wildcard media type (e.g. @image/*@), or a comma-separated list of the two types.
    Encoding -> Maybe MediaType
_encodingContentType :: Maybe MediaType

    -- | A map allowing additional information to be provided as headers,
    -- for example @Content-Disposition@. @Content-Type@ is described separately
    -- and SHALL be ignored in this section.
    -- This property SHALL be ignored if the request body media type is not a @multipart@.
  , Encoding -> InsOrdHashMap Text (Referenced Header)
_encodingHeaders :: InsOrdHashMap Text (Referenced Header)

    -- | Describes how a specific property value will be serialized depending on its type.
    -- See 'Param' Object for details on the style property.
    -- The behavior follows the same values as query parameters, including default values.
    -- This property SHALL be ignored if the request body media type
    -- is not @application/x-www-form-urlencoded@.
  , Encoding -> Maybe Style
_encodingStyle :: Maybe Style

    -- | When this is true, property values of type @array@ or @object@ generate
    -- separate parameters for each value of the array,
    -- or key-value-pair of the map.
    -- For other types of properties this property has no effect.
    -- When style is form, the default value is @true@. For all other styles,
    -- the default value is @false@. This property SHALL be ignored
    -- if the request body media type is not @application/x-www-form-urlencoded@.
  , Encoding -> Maybe Bool
_encodingExplode :: Maybe Bool

    -- | Determines whether the parameter value SHOULD allow reserved characters,
    -- as defined by [RFC3986](https://tools.ietf.org/html/rfc3986#section-2.2)
    -- @:/?#[]@!$&'()*+,;=@ to be included without percent-encoding.
    -- The default value is @false@. This property SHALL be ignored if the request body media type
    -- is not @application/x-www-form-urlencoded@.
  , Encoding -> Maybe Bool
_encodingAllowReserved :: Maybe Bool
  } deriving (Encoding -> Encoding -> Bool
(Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool) -> Eq Encoding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Encoding -> Encoding -> Bool
$c/= :: Encoding -> Encoding -> Bool
== :: Encoding -> Encoding -> Bool
$c== :: Encoding -> Encoding -> Bool
Eq, Int -> Encoding -> ShowS
[Encoding] -> ShowS
Encoding -> FilePath
(Int -> Encoding -> ShowS)
-> (Encoding -> FilePath) -> ([Encoding] -> ShowS) -> Show Encoding
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Encoding] -> ShowS
$cshowList :: [Encoding] -> ShowS
show :: Encoding -> FilePath
$cshow :: Encoding -> FilePath
showsPrec :: Int -> Encoding -> ShowS
$cshowsPrec :: Int -> Encoding -> ShowS
Show, (forall x. Encoding -> Rep Encoding x)
-> (forall x. Rep Encoding x -> Encoding) -> Generic Encoding
forall x. Rep Encoding x -> Encoding
forall x. Encoding -> Rep Encoding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Encoding x -> Encoding
$cfrom :: forall x. Encoding -> Rep Encoding x
Generic, Typeable Encoding
DataType
Constr
Typeable Encoding
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Encoding -> c Encoding)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Encoding)
-> (Encoding -> Constr)
-> (Encoding -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Encoding))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding))
-> ((forall b. Data b => b -> b) -> Encoding -> Encoding)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Encoding -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Encoding -> r)
-> (forall u. (forall d. Data d => d -> u) -> Encoding -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> Data Encoding
Encoding -> DataType
Encoding -> Constr
(forall b. Data b => b -> b) -> Encoding -> Encoding
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
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) -> Encoding -> u
forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Encoding)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding)
$cEncoding :: Constr
$tEncoding :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Encoding -> m Encoding
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
gmapMp :: (forall d. Data d => d -> m d) -> Encoding -> m Encoding
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
gmapM :: (forall d. Data d => d -> m d) -> Encoding -> m Encoding
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
gmapQi :: Int -> (forall d. Data d => d -> u) -> Encoding -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u
gmapQ :: (forall d. Data d => d -> u) -> Encoding -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
gmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding
$cgmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Encoding)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Encoding)
dataTypeOf :: Encoding -> DataType
$cdataTypeOf :: Encoding -> DataType
toConstr :: Encoding -> Constr
$ctoConstr :: Encoding -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
$cp1Data :: Typeable Encoding
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 FilePath
"MimeList" [FilePath
"getMimeList"] Fixity
Prefix

mimeListDataType :: DataType
mimeListDataType :: DataType
mimeListDataType = FilePath -> [Constr] -> DataType
mkDataType FilePath
"Data.OpenApi.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 forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
    Int
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 ([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))
    Int
_ -> FilePath -> c MimeList
forall a. HasCallStack => FilePath -> a
error (FilePath -> c MimeList) -> FilePath -> c MimeList
forall a b. (a -> b) -> a -> b
$ FilePath
"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]
++ FilePath
" is not of type MimeList."
  toConstr :: MimeList -> Constr
toConstr (MimeList [MediaType]
_) = Constr
mimeListConstr
  dataTypeOf :: MimeList -> DataType
dataTypeOf MimeList
_ = 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.
    -- CommonMark syntax MAY 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

    -- | Specifies that a parameter is deprecated and SHOULD be transitioned out of usage.
    -- Default value is @false@.
  , Param -> Maybe Bool
_paramDeprecated :: Maybe Bool

    -- | The location of the parameter.
  , Param -> ParamLocation
_paramIn :: ParamLocation

    -- | Sets the ability to pass empty-valued parameters.
    -- This is valid only for 'ParamQuery' parameters and allows sending
    -- a parameter with an empty value. Default value is @false@.
  , Param -> Maybe Bool
_paramAllowEmptyValue :: Maybe Bool

    -- | Determines whether the parameter value SHOULD allow reserved characters,
    -- as defined by [RFC3986](https://tools.ietf.org/html/rfc3986#section-2.2)
    -- @:/?#[]@!$&'()*+,;=@ to be included without percent-encoding.
    -- This property only applies to parameters with an '_paramIn' value of 'ParamQuery'.
    -- The default value is 'False'.
  , Param -> Maybe Bool
_paramAllowReserved :: Maybe Bool

    -- | Parameter schema.
  , Param -> Maybe (Referenced Schema)
_paramSchema :: Maybe (Referenced Schema)

    -- | Describes how the parameter value will be serialized depending
    -- on the type of the parameter value. Default values (based on value of '_paramIn'):
    -- for 'ParamQuery' - 'StyleForm'; for 'ParamPath' - 'StyleSimple'; for 'ParamHeader' - 'StyleSimple';
    -- for 'ParamCookie' - 'StyleForm'.
  , Param -> Maybe Style
_paramStyle :: Maybe Style

    -- | When this is true, parameter values of type @array@ or @object@
    -- generate separate parameters for each value of the array or key-value pair of the map.
    -- For other types of parameters this property has no effect.
    -- When style is @form@, the default value is true. For all other styles, the default value is false.
  , Param -> Maybe Bool
_paramExplode :: Maybe Bool

    -- | Example of the parameter's potential value.
    -- The example SHOULD match the specified schema and encoding properties if present.
    -- The '_paramExample' field is mutually exclusive of the '_paramExamples' field.
    -- Furthermore, if referencing a schema that contains an example, the example value
    -- SHALL override the example provided by the schema. To represent examples of media types
    -- that cannot naturally be represented in JSON or YAML, a string value can contain
    -- the example with escaping where necessary.
  , Param -> Maybe Value
_paramExample :: Maybe Value

    -- | Examples of the parameter's potential value.
    -- Each example SHOULD contain a value in the correct format as specified
    -- in the parameter encoding. The '_paramExamples' field is mutually exclusive of the '_paramExample' field.
    -- Furthermore, if referencing a schema that contains an example,
    -- the examples value SHALL override the example provided by the schema.
  , Param -> InsOrdHashMap Text (Referenced Example)
_paramExamples :: InsOrdHashMap Text (Referenced Example)

    -- TODO
    -- _paramContent :: InsOrdHashMap MediaType MediaTypeObject
    -- should be singleton. mutually exclusive with _paramSchema.
  } 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 Example = Example
  { -- | Short description for the example.
    Example -> Maybe Text
_exampleSummary :: Maybe Text

    -- | Long description for the example.
    -- CommonMark syntax MAY be used for rich text representation.
  , Example -> Maybe Text
_exampleDescription :: Maybe Text

    -- | Embedded literal example.
    -- The '_exampleValue' field and '_exampleExternalValue' field are mutually exclusive.
    --
    -- To represent examples of media types that cannot naturally represented in JSON or YAML,
    -- use a string value to contain the example, escaping where necessary.
  , Example -> Maybe Value
_exampleValue :: Maybe Value

    -- | A URL that points to the literal example.
    -- This provides the capability to reference examples that cannot easily be included
    -- in JSON or YAML documents. The '_exampleValue' field
    -- and '_exampleExternalValue' field are mutually exclusive.
  , Example -> Maybe URL
_exampleExternalValue :: Maybe URL
  } 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, Typeable Example
DataType
Constr
Typeable Example
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Example -> c Example)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Example)
-> (Example -> Constr)
-> (Example -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Example))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example))
-> ((forall b. Data b => b -> b) -> Example -> Example)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Example -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Example -> r)
-> (forall u. (forall d. Data d => d -> u) -> Example -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Example -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Example -> m Example)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Example -> m Example)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Example -> m Example)
-> Data Example
Example -> DataType
Example -> Constr
(forall b. Data b => b -> b) -> Example -> Example
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
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) -> Example -> u
forall u. (forall d. Data d => d -> u) -> Example -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Example -> m Example
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Example)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example)
$cExample :: Constr
$tExample :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Example -> m Example
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example
gmapMp :: (forall d. Data d => d -> m d) -> Example -> m Example
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example
gmapM :: (forall d. Data d => d -> m d) -> Example -> m Example
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Example -> m Example
gmapQi :: Int -> (forall d. Data d => d -> u) -> Example -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Example -> u
gmapQ :: (forall d. Data d => d -> u) -> Example -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Example -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
gmapT :: (forall b. Data b => b -> b) -> Example -> Example
$cgmapT :: (forall b. Data b => b -> b) -> Example -> Example
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Example)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Example)
dataTypeOf :: Example -> DataType
$cdataTypeOf :: Example -> DataType
toConstr :: Example -> Constr
$ctoConstr :: Example -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
$cp1Data :: Typeable Example
Data)

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

-- | The Link object represents a possible design-time link for a response.
-- The presence of a link does not guarantee the caller's ability to successfully invoke it,
-- rather it provides a known relationship and traversal mechanism between responses and other operations.
data Link = Link
  { -- | A relative or absolute URI reference to an OAS operation.
    -- This field is mutually exclusive of the '_linkOperationId' field,
    -- and MUST point to an 'Operation' Object. Relative '_linkOperationRef'
    -- values MAY be used to locate an existing 'Operation' Object in the OpenAPI definition.
    Link -> Maybe Text
_linkOperationRef :: Maybe Text

    -- | The name of an /existing/, resolvable OAS operation, as defined with a unique
    -- '_operationOperationId'. This field is mutually exclusive of the '_linkOperationRef' field.
  , Link -> Maybe Text
_linkOperationId :: Maybe Text

    -- | A map representing parameters to pass to an operation as specified with '_linkOperationId'
    -- or identified via '_linkOperationRef'. The key is the parameter name to be used, whereas
    -- the value can be a constant or an expression to be evaluated and passed to the linked operation.
    -- The parameter name can be qualified using the parameter location @[{in}.]{name}@
    -- for operations that use the same parameter name in different locations (e.g. path.id).
  , Link -> InsOrdHashMap Text ExpressionOrValue
_linkParameters :: InsOrdHashMap Text ExpressionOrValue

    -- | A literal value or @{expression}@ to use as a request body when calling the target operation.
  , Link -> Maybe ExpressionOrValue
_linkRequestBody :: Maybe ExpressionOrValue

    -- | A description of the link.
  , Link -> Maybe Text
_linkDescription :: Maybe Text

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

-- | Items for @'OpenApiArray'@ schemas.
--
-- __Warning__: OpenAPI 3.0 does not support tuple arrays. However, OpenAPI 3.1 will, as
-- it will incorporate Json Schema mostly verbatim.
--
-- @'OpenApiItemsObject'@ should be used to specify homogenous array @'Schema'@s.
--
-- @'OpenApiItemsArray'@ should be used to specify tuple @'Schema'@s.
data OpenApiItems where
  OpenApiItemsObject    :: Referenced Schema   -> OpenApiItems
  OpenApiItemsArray     :: [Referenced Schema] -> OpenApiItems
  deriving (OpenApiItems -> OpenApiItems -> Bool
(OpenApiItems -> OpenApiItems -> Bool)
-> (OpenApiItems -> OpenApiItems -> Bool) -> Eq OpenApiItems
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenApiItems -> OpenApiItems -> Bool
$c/= :: OpenApiItems -> OpenApiItems -> Bool
== :: OpenApiItems -> OpenApiItems -> Bool
$c== :: OpenApiItems -> OpenApiItems -> Bool
Eq, Int -> OpenApiItems -> ShowS
[OpenApiItems] -> ShowS
OpenApiItems -> FilePath
(Int -> OpenApiItems -> ShowS)
-> (OpenApiItems -> FilePath)
-> ([OpenApiItems] -> ShowS)
-> Show OpenApiItems
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OpenApiItems] -> ShowS
$cshowList :: [OpenApiItems] -> ShowS
show :: OpenApiItems -> FilePath
$cshow :: OpenApiItems -> FilePath
showsPrec :: Int -> OpenApiItems -> ShowS
$cshowsPrec :: Int -> OpenApiItems -> ShowS
Show, Typeable, Typeable OpenApiItems
DataType
Constr
Typeable OpenApiItems
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OpenApiItems)
-> (OpenApiItems -> Constr)
-> (OpenApiItems -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OpenApiItems))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OpenApiItems))
-> ((forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r)
-> (forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> Data OpenApiItems
OpenApiItems -> DataType
OpenApiItems -> Constr
(forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
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) -> OpenApiItems -> u
forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiItems)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems)
$cOpenApiItemsArray :: Constr
$cOpenApiItemsObject :: Constr
$tOpenApiItems :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
gmapMp :: (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
gmapM :: (forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
gmapQ :: (forall d. Data d => d -> u) -> OpenApiItems -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
gmapT :: (forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems
$cgmapT :: (forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OpenApiItems)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiItems)
dataTypeOf :: OpenApiItems -> DataType
$cdataTypeOf :: OpenApiItems -> DataType
toConstr :: OpenApiItems -> Constr
$ctoConstr :: OpenApiItems -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
$cp1Data :: Typeable OpenApiItems
Data)

data OpenApiType where
  OpenApiString   :: OpenApiType
  OpenApiNumber   :: OpenApiType
  OpenApiInteger  :: OpenApiType
  OpenApiBoolean  :: OpenApiType
  OpenApiArray    :: OpenApiType
  OpenApiNull     :: OpenApiType
  OpenApiObject   :: OpenApiType
  deriving (OpenApiType -> OpenApiType -> Bool
(OpenApiType -> OpenApiType -> Bool)
-> (OpenApiType -> OpenApiType -> Bool) -> Eq OpenApiType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenApiType -> OpenApiType -> Bool
$c/= :: OpenApiType -> OpenApiType -> Bool
== :: OpenApiType -> OpenApiType -> Bool
$c== :: OpenApiType -> OpenApiType -> Bool
Eq, Int -> OpenApiType -> ShowS
[OpenApiType] -> ShowS
OpenApiType -> FilePath
(Int -> OpenApiType -> ShowS)
-> (OpenApiType -> FilePath)
-> ([OpenApiType] -> ShowS)
-> Show OpenApiType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OpenApiType] -> ShowS
$cshowList :: [OpenApiType] -> ShowS
show :: OpenApiType -> FilePath
$cshow :: OpenApiType -> FilePath
showsPrec :: Int -> OpenApiType -> ShowS
$cshowsPrec :: Int -> OpenApiType -> ShowS
Show, Typeable, (forall x. OpenApiType -> Rep OpenApiType x)
-> (forall x. Rep OpenApiType x -> OpenApiType)
-> Generic OpenApiType
forall x. Rep OpenApiType x -> OpenApiType
forall x. OpenApiType -> Rep OpenApiType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenApiType x -> OpenApiType
$cfrom :: forall x. OpenApiType -> Rep OpenApiType x
Generic, Typeable OpenApiType
DataType
Constr
Typeable OpenApiType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> OpenApiType -> c OpenApiType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OpenApiType)
-> (OpenApiType -> Constr)
-> (OpenApiType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OpenApiType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OpenApiType))
-> ((forall b. Data b => b -> b) -> OpenApiType -> OpenApiType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OpenApiType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OpenApiType -> r)
-> (forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OpenApiType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> Data OpenApiType
OpenApiType -> DataType
OpenApiType -> Constr
(forall b. Data b => b -> b) -> OpenApiType -> OpenApiType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
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) -> OpenApiType -> u
forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType)
$cOpenApiObject :: Constr
$cOpenApiNull :: Constr
$cOpenApiArray :: Constr
$cOpenApiBoolean :: Constr
$cOpenApiInteger :: Constr
$cOpenApiNumber :: Constr
$cOpenApiString :: Constr
$tOpenApiType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
gmapMp :: (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
gmapM :: (forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
gmapQ :: (forall d. Data d => d -> u) -> OpenApiType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
gmapT :: (forall b. Data b => b -> b) -> OpenApiType -> OpenApiType
$cgmapT :: (forall b. Data b => b -> b) -> OpenApiType -> OpenApiType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OpenApiType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiType)
dataTypeOf :: OpenApiType -> DataType
$cdataTypeOf :: OpenApiType -> DataType
toConstr :: OpenApiType -> Constr
$ctoConstr :: OpenApiType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
$cp1Data :: Typeable OpenApiType
Data)

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 pass a specific cookie value to the API.
  | ParamCookie
  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)
$cParamCookie :: 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

type ParamName = Text

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

  , Schema -> Maybe Bool
_schemaNullable :: Maybe Bool
  , Schema -> Maybe [Referenced Schema]
_schemaAllOf :: Maybe [Referenced Schema]
  , Schema -> Maybe [Referenced Schema]
_schemaOneOf :: Maybe [Referenced Schema]
  , Schema -> Maybe (Referenced Schema)
_schemaNot :: Maybe (Referenced Schema)
  , Schema -> Maybe [Referenced Schema]
_schemaAnyOf :: Maybe [Referenced Schema]
  , Schema -> InsOrdHashMap Text (Referenced Schema)
_schemaProperties :: InsOrdHashMap Text (Referenced Schema)
  , Schema -> Maybe AdditionalProperties
_schemaAdditionalProperties :: Maybe AdditionalProperties

  , Schema -> Maybe Discriminator
_schemaDiscriminator :: Maybe Discriminator
  , Schema -> Maybe Bool
_schemaReadOnly :: Maybe Bool
  , Schema -> Maybe Bool
_schemaWriteOnly :: Maybe Bool
  , Schema -> Maybe Xml
_schemaXml :: Maybe Xml
  , Schema -> Maybe ExternalDocs
_schemaExternalDocs :: Maybe ExternalDocs
  , Schema -> Maybe Value
_schemaExample :: Maybe Value
  , Schema -> Maybe Bool
_schemaDeprecated :: Maybe Bool

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

  , -- | 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.
    Schema -> Maybe Value
_schemaDefault :: Maybe Value

  , Schema -> Maybe OpenApiType
_schemaType :: Maybe OpenApiType
  , Schema -> Maybe Text
_schemaFormat :: Maybe Format
  , Schema -> Maybe OpenApiItems
_schemaItems :: Maybe OpenApiItems
  , Schema -> Maybe Scientific
_schemaMaximum :: Maybe Scientific
  , Schema -> Maybe Bool
_schemaExclusiveMaximum :: Maybe Bool
  , Schema -> Maybe Scientific
_schemaMinimum :: Maybe Scientific
  , Schema -> Maybe Bool
_schemaExclusiveMinimum :: Maybe Bool
  , Schema -> Maybe Integer
_schemaMaxLength :: Maybe Integer
  , Schema -> Maybe Integer
_schemaMinLength :: Maybe Integer
  , Schema -> Maybe Text
_schemaPattern :: Maybe Pattern
  , Schema -> Maybe Integer
_schemaMaxItems :: Maybe Integer
  , Schema -> Maybe Integer
_schemaMinItems :: Maybe Integer
  , Schema -> Maybe Bool
_schemaUniqueItems :: Maybe Bool
  , Schema -> Maybe [Value]
_schemaEnum :: Maybe [Value]
  , Schema -> Maybe Scientific
_schemaMultipleOf :: Maybe Scientific
  } 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)

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

data Discriminator = Discriminator
  { -- | The name of the property in the payload that will hold the discriminator value.
    Discriminator -> Text
_discriminatorPropertyName :: Text

    -- | An object to hold mappings between payload values and schema names or references.
  , Discriminator -> InsOrdHashMap Text Text
_discriminatorMapping :: InsOrdHashMap Text Text
  } deriving (Discriminator -> Discriminator -> Bool
(Discriminator -> Discriminator -> Bool)
-> (Discriminator -> Discriminator -> Bool) -> Eq Discriminator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Discriminator -> Discriminator -> Bool
$c/= :: Discriminator -> Discriminator -> Bool
== :: Discriminator -> Discriminator -> Bool
$c== :: Discriminator -> Discriminator -> Bool
Eq, Int -> Discriminator -> ShowS
[Discriminator] -> ShowS
Discriminator -> FilePath
(Int -> Discriminator -> ShowS)
-> (Discriminator -> FilePath)
-> ([Discriminator] -> ShowS)
-> Show Discriminator
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Discriminator] -> ShowS
$cshowList :: [Discriminator] -> ShowS
show :: Discriminator -> FilePath
$cshow :: Discriminator -> FilePath
showsPrec :: Int -> Discriminator -> ShowS
$cshowsPrec :: Int -> Discriminator -> ShowS
Show, (forall x. Discriminator -> Rep Discriminator x)
-> (forall x. Rep Discriminator x -> Discriminator)
-> Generic Discriminator
forall x. Rep Discriminator x -> Discriminator
forall x. Discriminator -> Rep Discriminator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Discriminator x -> Discriminator
$cfrom :: forall x. Discriminator -> Rep Discriminator x
Generic, Typeable Discriminator
DataType
Constr
Typeable Discriminator
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Discriminator -> c Discriminator)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Discriminator)
-> (Discriminator -> Constr)
-> (Discriminator -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Discriminator))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Discriminator))
-> ((forall b. Data b => b -> b) -> Discriminator -> Discriminator)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Discriminator -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Discriminator -> r)
-> (forall u. (forall d. Data d => d -> u) -> Discriminator -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Discriminator -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> Data Discriminator
Discriminator -> DataType
Discriminator -> Constr
(forall b. Data b => b -> b) -> Discriminator -> Discriminator
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
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) -> Discriminator -> u
forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Discriminator)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator)
$cDiscriminator :: Constr
$tDiscriminator :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
gmapMp :: (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
gmapM :: (forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
gmapQi :: Int -> (forall d. Data d => d -> u) -> Discriminator -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Discriminator -> u
gmapQ :: (forall d. Data d => d -> u) -> Discriminator -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
gmapT :: (forall b. Data b => b -> b) -> Discriminator -> Discriminator
$cgmapT :: (forall b. Data b => b -> b) -> Discriminator -> Discriminator
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Discriminator)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Discriminator)
dataTypeOf :: Discriminator -> DataType
$cdataTypeOf :: Discriminator -> DataType
toConstr :: Discriminator -> Constr
$ctoConstr :: Discriminator -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
$cp1Data :: Typeable Discriminator
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)

data Xml = Xml
  { -- | Replaces the name of the element/attribute used for the described schema property.
    -- When defined within the @'OpenApiItems'@ (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.
    -- [CommonMark syntax](https://spec.commonmark.org/) can be used for rich text representation.
    Response -> Text
_responseDescription :: Text

    -- | A map containing descriptions of potential response payloads.
    -- The key is a media type or media type range and the value describes it.
    -- For responses that match multiple keys, only the most specific key is applicable.
    -- e.g. @text/plain@ overrides @text/*@.
  , Response -> InsOrdHashMap MediaType MediaTypeObject
_responseContent :: InsOrdHashMap MediaType MediaTypeObject

    -- | Maps a header name to its definition.
  , Response -> InsOrdHashMap Text (Referenced Header)
_responseHeaders :: InsOrdHashMap HeaderName (Referenced Header)

    -- | A map of operations links that can be followed from the response.
    -- The key of the map is a short name for the link, following the naming
    -- constraints of the names for 'Component' Objects.
  , Response -> InsOrdHashMap Text (Referenced Link)
_responseLinks :: InsOrdHashMap Text (Referenced Link)
  } 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 FilePath
s = Text
-> InsOrdHashMap MediaType MediaTypeObject
-> InsOrdHashMap Text (Referenced Header)
-> InsOrdHashMap Text (Referenced Link)
-> Response
Response (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) InsOrdHashMap MediaType MediaTypeObject
forall a. Monoid a => a
mempty InsOrdHashMap Text (Referenced Header)
forall a. Monoid a => a
mempty InsOrdHashMap Text (Referenced Link)
forall a. Monoid a => a
mempty

-- | A map of possible out-of band callbacks related to the parent operation.
-- Each value in the map is a 'PathItem' Object that describes a set of requests that
-- may be initiated by the API provider and the expected responses.
-- The key value used to identify the path item object is an expression, evaluated at runtime,
-- that identifies a URL to use for the callback operation.
newtype Callback = Callback (InsOrdHashMap Text PathItem)
  deriving (Callback -> Callback -> Bool
(Callback -> Callback -> Bool)
-> (Callback -> Callback -> Bool) -> Eq Callback
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Callback -> Callback -> Bool
$c/= :: Callback -> Callback -> Bool
== :: Callback -> Callback -> Bool
$c== :: Callback -> Callback -> Bool
Eq, Int -> Callback -> ShowS
[Callback] -> ShowS
Callback -> FilePath
(Int -> Callback -> ShowS)
-> (Callback -> FilePath) -> ([Callback] -> ShowS) -> Show Callback
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Callback] -> ShowS
$cshowList :: [Callback] -> ShowS
show :: Callback -> FilePath
$cshow :: Callback -> FilePath
showsPrec :: Int -> Callback -> ShowS
$cshowsPrec :: Int -> Callback -> ShowS
Show, (forall x. Callback -> Rep Callback x)
-> (forall x. Rep Callback x -> Callback) -> Generic Callback
forall x. Rep Callback x -> Callback
forall x. Callback -> Rep Callback x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Callback x -> Callback
$cfrom :: forall x. Callback -> Rep Callback x
Generic, Typeable Callback
DataType
Constr
Typeable Callback
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Callback -> c Callback)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Callback)
-> (Callback -> Constr)
-> (Callback -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Callback))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback))
-> ((forall b. Data b => b -> b) -> Callback -> Callback)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Callback -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Callback -> r)
-> (forall u. (forall d. Data d => d -> u) -> Callback -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Callback -> m Callback)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Callback -> m Callback)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Callback -> m Callback)
-> Data Callback
Callback -> DataType
Callback -> Constr
(forall b. Data b => b -> b) -> Callback -> Callback
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
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) -> Callback -> u
forall u. (forall d. Data d => d -> u) -> Callback -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Callback)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback)
$cCallback :: Constr
$tCallback :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Callback -> m Callback
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
gmapMp :: (forall d. Data d => d -> m d) -> Callback -> m Callback
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
gmapM :: (forall d. Data d => d -> m d) -> Callback -> m Callback
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
gmapQi :: Int -> (forall d. Data d => d -> u) -> Callback -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u
gmapQ :: (forall d. Data d => d -> u) -> Callback -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Callback -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
gmapT :: (forall b. Data b => b -> b) -> Callback -> Callback
$cgmapT :: (forall b. Data b => b -> b) -> Callback -> Callback
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Callback)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Callback)
dataTypeOf :: Callback -> DataType
$cdataTypeOf :: Callback -> DataType
toConstr :: Callback -> Constr
$ctoConstr :: Callback -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
$cp1Data :: Typeable Callback
Data, Typeable)

type HeaderName = Text

-- | Header fields have the same meaning as for 'Param'.
--
-- Style is always treated as 'StyleSimple', as it is the only value allowed for headers.
data Header = Header
  { -- | A short description of the header.
    Header -> Maybe Text
_headerDescription :: Maybe HeaderName

  , Header -> Maybe Bool
_headerRequired :: Maybe Bool
  , Header -> Maybe Bool
_headerDeprecated :: Maybe Bool
  , Header -> Maybe Bool
_headerAllowEmptyValue :: Maybe Bool
  , Header -> Maybe Bool
_headerExplode :: Maybe Bool
  , Header -> Maybe Value
_headerExample :: Maybe Value
  , Header -> InsOrdHashMap Text (Referenced Example)
_headerExamples :: InsOrdHashMap Text (Referenced Example)

  , Header -> Maybe (Referenced Schema)
_headerSchema :: Maybe (Referenced Schema)
  } 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)

-- | The location of the API key.
data ApiKeyLocation
  = ApiKeyQuery
  | ApiKeyHeader
  | ApiKeyCookie
  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)
$cApiKeyCookie :: Constr
$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

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

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

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

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

data OAuth2Flow p = OAuth2Flow
  { OAuth2Flow p -> p
_oAuth2Params :: p

    -- | The URL to be used for obtaining refresh tokens.
  , OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl :: Maybe URL

    -- | The available scopes for the OAuth2 security scheme.
    -- A map between the scope name and a short description for it.
    -- The map MAY be empty.
  , OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes :: InsOrdHashMap Text Text
  } deriving (OAuth2Flow p -> OAuth2Flow p -> Bool
(OAuth2Flow p -> OAuth2Flow p -> Bool)
-> (OAuth2Flow p -> OAuth2Flow p -> Bool) -> Eq (OAuth2Flow p)
forall p. Eq p => OAuth2Flow p -> OAuth2Flow p -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OAuth2Flow p -> OAuth2Flow p -> Bool
$c/= :: forall p. Eq p => OAuth2Flow p -> OAuth2Flow p -> Bool
== :: OAuth2Flow p -> OAuth2Flow p -> Bool
$c== :: forall p. Eq p => OAuth2Flow p -> OAuth2Flow p -> Bool
Eq, Int -> OAuth2Flow p -> ShowS
[OAuth2Flow p] -> ShowS
OAuth2Flow p -> FilePath
(Int -> OAuth2Flow p -> ShowS)
-> (OAuth2Flow p -> FilePath)
-> ([OAuth2Flow p] -> ShowS)
-> Show (OAuth2Flow p)
forall p. Show p => Int -> OAuth2Flow p -> ShowS
forall p. Show p => [OAuth2Flow p] -> ShowS
forall p. Show p => OAuth2Flow p -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OAuth2Flow p] -> ShowS
$cshowList :: forall p. Show p => [OAuth2Flow p] -> ShowS
show :: OAuth2Flow p -> FilePath
$cshow :: forall p. Show p => OAuth2Flow p -> FilePath
showsPrec :: Int -> OAuth2Flow p -> ShowS
$cshowsPrec :: forall p. Show p => Int -> OAuth2Flow p -> ShowS
Show, (forall x. OAuth2Flow p -> Rep (OAuth2Flow p) x)
-> (forall x. Rep (OAuth2Flow p) x -> OAuth2Flow p)
-> Generic (OAuth2Flow p)
forall x. Rep (OAuth2Flow p) x -> OAuth2Flow p
forall x. OAuth2Flow p -> Rep (OAuth2Flow p) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p x. Rep (OAuth2Flow p) x -> OAuth2Flow p
forall p x. OAuth2Flow p -> Rep (OAuth2Flow p) x
$cto :: forall p x. Rep (OAuth2Flow p) x -> OAuth2Flow p
$cfrom :: forall p x. OAuth2Flow p -> Rep (OAuth2Flow p) x
Generic, Typeable (OAuth2Flow p)
DataType
Constr
Typeable (OAuth2Flow p)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p))
-> (OAuth2Flow p -> Constr)
-> (OAuth2Flow p -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (OAuth2Flow p)))
-> ((forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r)
-> (forall u. (forall d. Data d => d -> u) -> OAuth2Flow p -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> Data (OAuth2Flow p)
OAuth2Flow p -> DataType
OAuth2Flow p -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
forall p. Data p => Typeable (OAuth2Flow p)
forall p. Data p => OAuth2Flow p -> DataType
forall p. Data p => OAuth2Flow p -> Constr
forall p.
Data p =>
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
forall p u.
Data p =>
Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
forall p u.
Data p =>
(forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
forall p r r'.
Data p =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall p r r'.
Data p =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall p (m :: * -> *).
(Data p, Monad m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall p (m :: * -> *).
(Data p, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall p (c :: * -> *).
Data p =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
forall p (c :: * -> *).
Data p =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
forall p (t :: * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
forall p (t :: * -> * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
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 p -> u
forall u. (forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
$cOAuth2Flow :: Constr
$tOAuth2Flow :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
$cgmapMo :: forall p (m :: * -> *).
(Data p, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
gmapMp :: (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
$cgmapMp :: forall p (m :: * -> *).
(Data p, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
gmapM :: (forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
$cgmapM :: forall p (m :: * -> *).
(Data p, Monad m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
$cgmapQi :: forall p u.
Data p =>
Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
gmapQ :: (forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
$cgmapQ :: forall p u.
Data p =>
(forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
$cgmapQr :: forall p r r'.
Data p =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
$cgmapQl :: forall p r r'.
Data p =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
gmapT :: (forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
$cgmapT :: forall p.
Data p =>
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
$cdataCast2 :: forall p (t :: * -> * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
$cdataCast1 :: forall p (t :: * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
dataTypeOf :: OAuth2Flow p -> DataType
$cdataTypeOf :: forall p. Data p => OAuth2Flow p -> DataType
toConstr :: OAuth2Flow p -> Constr
$ctoConstr :: forall p. Data p => OAuth2Flow p -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
$cgunfold :: forall p (c :: * -> *).
Data p =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
$cgfoldl :: forall p (c :: * -> *).
Data p =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
$cp1Data :: forall p. Data p => Typeable (OAuth2Flow p)
Data, Typeable)

data OAuth2Flows = OAuth2Flows
  { -- | Configuration for the OAuth Implicit flow
    OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit :: Maybe (OAuth2Flow OAuth2ImplicitFlow)

    -- | Configuration for the OAuth Resource Owner Password flow
  , OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword :: Maybe (OAuth2Flow OAuth2PasswordFlow)

    -- | Configuration for the OAuth Client Credentials flow
  , OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials :: Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)

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

type BearerFormat = Text

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

-- |
--
-- >>> BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeBearer Nothing))
-- {
--     "scheme": "bearer",
--     "type": "http"
-- }
--
-- >>> BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeBearer (Just "jwt")))
-- {
--     "bearerFormat": "jwt",
--     "scheme": "bearer",
--     "type": "http"
-- }
--
-- >>> BSL.putStrLn $ encodePretty (SecuritySchemeHttp HttpSchemeBasic)
-- {
--     "scheme": "basic",
--     "type": "http"
-- }
--
-- >>> BSL.putStrLn $ encodePretty (SecuritySchemeHttp (HttpSchemeCustom "CANARY"))
-- {
--     "scheme": "CANARY",
--     "type": "http"
-- }
--
-- >>> BSL.putStrLn $ encodePretty (SecuritySchemeApiKey (ApiKeyParams "id" ApiKeyCookie))
-- {
--     "in": "cookie",
--     "name": "id",
--     "type": "apiKey"
-- }
--
data SecuritySchemeType
  = SecuritySchemeHttp HttpSchemeType
  | SecuritySchemeApiKey ApiKeyParams
  | SecuritySchemeOAuth2 OAuth2Flows
  | SecuritySchemeOpenIdConnect URL
  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)
$cSecuritySchemeOpenIdConnect :: Constr
$cSecuritySchemeOAuth2 :: Constr
$cSecuritySchemeApiKey :: Constr
$cSecuritySchemeHttp :: 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)

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.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY 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 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.
    -- [CommonMark syntax](https://spec.commonmark.org/) MAY 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 ''Server
deriveGeneric ''Components
deriveGeneric ''Header
deriveGeneric ''OAuth2Flow
deriveGeneric ''OAuth2Flows
deriveGeneric ''Operation
deriveGeneric ''Param
deriveGeneric ''PathItem
deriveGeneric ''Response
deriveGeneric ''RequestBody
deriveGeneric ''MediaTypeObject
deriveGeneric ''Responses
deriveGeneric ''SecurityScheme
deriveGeneric ''Schema
deriveGeneric ''OpenApi
deriveGeneric ''Example
deriveGeneric ''Encoding
deriveGeneric ''Link

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

instance Semigroup OpenApi where
  <> :: OpenApi -> OpenApi -> OpenApi
(<>) = OpenApi -> OpenApi -> OpenApi
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid OpenApi where
  mempty :: OpenApi
mempty = OpenApi
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: OpenApi -> OpenApi -> OpenApi
mappend = OpenApi -> OpenApi -> OpenApi
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 Components where
  <> :: Components -> Components -> Components
(<>) = Components -> Components -> Components
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Components where
  mempty :: Components
mempty = Components
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Components -> Components -> Components
mappend = Components -> Components -> Components
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 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 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 MediaTypeObject where
  <> :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
(<>) = MediaTypeObject -> MediaTypeObject -> MediaTypeObject
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid MediaTypeObject where
  mempty :: MediaTypeObject
mempty = MediaTypeObject
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
mappend = MediaTypeObject -> MediaTypeObject -> MediaTypeObject
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Encoding where
  <> :: Encoding -> Encoding -> Encoding
(<>) = Encoding -> Encoding -> Encoding
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Encoding where
  mempty :: Encoding
mempty = Encoding
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
  mappend :: Encoding -> Encoding -> Encoding
mappend = Encoding -> Encoding -> Encoding
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 (OAuth2Flow p) where
  l :: OAuth2Flow p
l@OAuth2Flow{ _oAath2RefreshUrl :: forall p. OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl = Maybe URL
lUrl, _oAuth2Scopes :: forall p. OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes = InsOrdHashMap Text Text
lScopes }
    <> :: OAuth2Flow p -> OAuth2Flow p -> OAuth2Flow p
<> OAuth2Flow { _oAath2RefreshUrl :: forall p. OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl = Maybe URL
rUrl, _oAuth2Scopes :: forall p. OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes = InsOrdHashMap Text Text
rScopes } =
      OAuth2Flow p
l { _oAath2RefreshUrl :: Maybe URL
_oAath2RefreshUrl = Maybe URL -> Maybe URL -> Maybe URL
forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Maybe URL
lUrl Maybe URL
rUrl, _oAuth2Scopes :: InsOrdHashMap Text Text
_oAuth2Scopes = InsOrdHashMap Text Text
lScopes InsOrdHashMap Text Text
-> InsOrdHashMap Text Text -> InsOrdHashMap Text Text
forall a. Semigroup a => a -> a -> a
<> InsOrdHashMap Text Text
rScopes }

-- swaggerMappend has First-like semantics, and here we need mappend'ing under Maybes.
instance Semigroup OAuth2Flows where
  OAuth2Flows
l <> :: OAuth2Flows -> OAuth2Flows -> OAuth2Flows
<> OAuth2Flows
r = OAuth2Flows :: Maybe (OAuth2Flow OAuth2ImplicitFlow)
-> Maybe (OAuth2Flow OAuth2PasswordFlow)
-> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
-> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
-> OAuth2Flows
OAuth2Flows
    { _oAuth2FlowsImplicit :: Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit = OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit OAuth2Flows
l Maybe (OAuth2Flow OAuth2ImplicitFlow)
-> Maybe (OAuth2Flow OAuth2ImplicitFlow)
-> Maybe (OAuth2Flow OAuth2ImplicitFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit OAuth2Flows
r
    , _oAuth2FlowsPassword :: Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword = OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword OAuth2Flows
l Maybe (OAuth2Flow OAuth2PasswordFlow)
-> Maybe (OAuth2Flow OAuth2PasswordFlow)
-> Maybe (OAuth2Flow OAuth2PasswordFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword OAuth2Flows
r
    , _oAuth2FlowsClientCredentials :: Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials = OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials OAuth2Flows
l Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
-> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
-> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials OAuth2Flows
r
    , _oAuth2FlowsAuthorizationCode :: Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode = OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode OAuth2Flows
l Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
-> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
-> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode OAuth2Flows
r
    }

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

instance Semigroup SecurityScheme where
  SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
lFlows) Maybe Text
lDesc
    <> :: SecurityScheme -> SecurityScheme -> SecurityScheme
<> SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
rFlows) Maybe Text
rDesc =
      SecuritySchemeType -> Maybe Text -> SecurityScheme
SecurityScheme (OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Flows -> SecuritySchemeType)
-> OAuth2Flows -> SecuritySchemeType
forall a b. (a -> b) -> a -> b
$ OAuth2Flows
lFlows OAuth2Flows -> OAuth2Flows -> OAuth2Flows
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows
rFlows) (Maybe Text -> Maybe Text -> Maybe Text
forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Maybe Text
lDesc Maybe Text
rDesc)
  SecurityScheme
l <> SecurityScheme
_ = SecurityScheme
l

instance Semigroup SecurityDefinitions where
  (SecurityDefinitions Definitions SecurityScheme
sd1) <> :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
<> (SecurityDefinitions 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
(<>)

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

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

instance SwaggerMonoid Info
instance SwaggerMonoid Components
instance SwaggerMonoid PathItem
instance SwaggerMonoid Schema
instance SwaggerMonoid Param
instance SwaggerMonoid Responses
instance SwaggerMonoid Response
instance SwaggerMonoid ExternalDocs
instance SwaggerMonoid Operation
instance (Eq a, Hashable a) => SwaggerMonoid (InsOrdHashSet a)

instance SwaggerMonoid MimeList
deriving instance SwaggerMonoid URL

instance SwaggerMonoid OpenApiType where
  swaggerMempty :: OpenApiType
swaggerMempty = OpenApiType
OpenApiString
  swaggerMappend :: OpenApiType -> OpenApiType -> OpenApiType
swaggerMappend OpenApiType
_ OpenApiType
y = OpenApiType
y

instance SwaggerMonoid ParamLocation where
  swaggerMempty :: ParamLocation
swaggerMempty = ParamLocation
ParamQuery
  swaggerMappend :: ParamLocation -> ParamLocation -> ParamLocation
swaggerMappend ParamLocation
_ 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 a
x) (Inline 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 Referenced a
_ Referenced a
y = Referenced a
y

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

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

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

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 FilePath
"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 FilePath
"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 FilePath
"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 FilePath
"License")

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

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 FilePath
"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 FilePath
"apiKey")

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 FilePath
"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 FilePath
"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 FilePath
"Xml")

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

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

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

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

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

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

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

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

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 FilePath
"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 FilePath
"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 FilePath
"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 FilePath
"License")

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

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 FilePath
"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 FilePath
"apiKey")

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 FilePath
"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 FilePath
"ExternalDocs")

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

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

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

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

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

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

instance ToJSON MediaType where
  toJSON :: MediaType -> Value
toJSON = FilePath -> Value
forall a. ToJSON a => a -> Value
toJSON (FilePath -> Value)
-> (MediaType -> FilePath) -> MediaType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show
  toEncoding :: MediaType -> Encoding
toEncoding = FilePath -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (FilePath -> Encoding)
-> (MediaType -> FilePath) -> MediaType -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show

instance ToJSONKey MediaType where
  toJSONKey :: ToJSONKeyFunction MediaType
toJSONKey = (MediaType -> Text) -> ToJSONKeyFunction MediaType
forall a. (a -> Text) -> ToJSONKeyFunction a
JSON.toJSONKeyText (FilePath -> Text
Text.pack (FilePath -> Text) -> (MediaType -> FilePath) -> MediaType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show)

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

instance ToJSON OAuth2Flows where
  toJSON :: OAuth2Flows -> Value
toJSON = OAuth2Flows -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: OAuth2Flows -> Encoding
toEncoding = OAuth2Flows -> 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 (SecuritySchemeHttp HttpSchemeType
ty) = case HttpSchemeType
ty of
    HttpSchemeBearer Maybe Text
mFmt ->
      [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"http" :: Text)
               , Text
"scheme" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"bearer" :: Text)
               ] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
t -> [Text
"bearerFormat" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
t]) Maybe Text
mFmt
    HttpSchemeType
HttpSchemeBasic ->
      [Pair] -> Value
object [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"http" :: Text)
             , Text
"scheme" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"basic" :: Text)
             ]
    HttpSchemeCustom Text
t ->
      [Pair] -> Value
object [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"http" :: Text)
             , Text
"scheme" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
t
             ]
  toJSON (SecuritySchemeApiKey ApiKeyParams
params)
      = ApiKeyParams -> Value
forall a. ToJSON a => a -> Value
toJSON ApiKeyParams
params
    Value -> Value -> Value
<+> [Pair] -> Value
object [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"apiKey" :: Text) ]
  toJSON (SecuritySchemeOAuth2 OAuth2Flows
params) = [Pair] -> Value
object
    [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"oauth2" :: Text)
    , Text
"flows" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= OAuth2Flows -> Value
forall a. ToJSON a => a -> Value
toJSON OAuth2Flows
params
    ]
  toJSON (SecuritySchemeOpenIdConnect URL
url) = [Pair] -> Value
object
    [ Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"openIdConnect" :: Text)
    , Text
"openIdConnectUrl" Text -> URL -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= URL
url
    ]

instance ToJSON OpenApi where
  toJSON :: OpenApi -> Value
toJSON OpenApi
a = OpenApi -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON OpenApi
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 (OpenApi -> InsOrdHashMap FilePath PathItem
_openApiPaths OpenApi
a)
    then (Value -> Value -> Value
<+> [Pair] -> Value
object [Text
"paths" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object []])
    else Value -> Value
forall a. a -> a
id
  toEncoding :: OpenApi -> Encoding
toEncoding = OpenApi -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON Server where
  toJSON :: Server -> Value
toJSON = Server -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Server -> Encoding
toEncoding = Server -> 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 = SwaggerAesonOptions -> Schema -> 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 -> Schema -> Value)
-> SwaggerAesonOptions -> Schema -> Value
forall a b. (a -> b) -> a -> b
$
      FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"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
?~ FilePath
"items"

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>.
--
-- >>> BSL.putStrLn $ encodePretty (OpenApiItemsArray [])
-- {
--     "example": [],
--     "items": {},
--     "maxItems": 0
-- }
--
instance ToJSON OpenApiItems where
  toJSON :: OpenApiItems -> Value
toJSON (OpenApiItemsObject Referenced Schema
x) = [Pair] -> Value
object [ Text
"items" Text -> Referenced Schema -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Referenced Schema
x ]
  toJSON (OpenApiItemsArray  []) = [Pair] -> Value
object
    [ Text
"items" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object []
    , Text
"maxItems" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Int
0 :: Int)
    , Text
"example" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Array -> Value
Array Array
forall a. Monoid a => a
mempty
    ]
  toJSON (OpenApiItemsArray  [Referenced Schema]
x) = [Pair] -> Value
object [ Text
"items" Text -> [Referenced Schema] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Referenced Schema]
x ]

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

instance ToJSON MimeList where
  toJSON :: MimeList -> Value
toJSON (MimeList [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 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 RequestBody where
  toJSON :: RequestBody -> Value
toJSON = RequestBody -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: RequestBody -> Encoding
toEncoding = RequestBody -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

instance ToJSON MediaTypeObject where
  toJSON :: MediaTypeObject -> Value
toJSON = MediaTypeObject -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: MediaTypeObject -> Encoding
toEncoding = MediaTypeObject -> 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 = Example -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
  toEncoding :: Example -> Encoding
toEncoding = Example -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
 All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding

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

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

instance ToJSON SecurityDefinitions where
  toJSON :: SecurityDefinitions -> Value
toJSON (SecurityDefinitions 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 Text
ref) = [Pair] -> Value
object [ Text
"$ref" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
ref ]

referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
referencedToJSON :: Text -> Referenced a -> Value
referencedToJSON Text
prefix (Ref (Reference Text
ref)) = [Pair] -> Value
object [ Text
"$ref" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref) ]
referencedToJSON Text
_ (Inline 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 Text
"#/components/schemas/"
instance ToJSON (Referenced Param)    where toJSON :: Referenced Param -> Value
toJSON = Text -> Referenced Param -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/parameters/"
instance ToJSON (Referenced Response) where toJSON :: Referenced Response -> Value
toJSON = Text -> Referenced Response -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/responses/"
instance ToJSON (Referenced RequestBody) where toJSON :: Referenced RequestBody -> Value
toJSON = Text -> Referenced RequestBody -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/requestBodies/"
instance ToJSON (Referenced Example)  where toJSON :: Referenced Example -> Value
toJSON = Text -> Referenced Example -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/examples/"
instance ToJSON (Referenced Header)   where toJSON :: Referenced Header -> Value
toJSON = Text -> Referenced Header -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/headers/"
instance ToJSON (Referenced Link)     where toJSON :: Referenced Link -> Value
toJSON = Text -> Referenced Link -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/links/"
instance ToJSON (Referenced Callback) where toJSON :: Referenced Callback -> Value
toJSON = Text -> Referenced Callback -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/callbacks/"

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

instance ToJSON ExpressionOrValue where
  toJSON :: ExpressionOrValue -> Value
toJSON (Expression Text
expr) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
expr
  toJSON (Value Value
val) = Value -> Value
forall a. ToJSON a => a -> Value
toJSON Value
val

instance ToJSON Callback where
  toJSON :: Callback -> Value
toJSON (Callback InsOrdHashMap Text PathItem
ps) = InsOrdHashMap Text PathItem -> Value
forall a. ToJSON a => a -> Value
toJSON InsOrdHashMap Text PathItem
ps

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

instance FromJSON MediaType where
  parseJSON :: Value -> Parser MediaType
parseJSON = FilePath -> (Text -> Parser MediaType) -> Value -> Parser MediaType
forall a. FilePath -> (Text -> Parser a) -> Value -> Parser a
withText FilePath
"MediaType" ((Text -> Parser MediaType) -> Value -> Parser MediaType)
-> (Text -> Parser MediaType) -> Value -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ \Text
str ->
    Parser MediaType
-> (MediaType -> Parser MediaType)
-> Maybe MediaType
-> Parser MediaType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> Parser MediaType
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser MediaType) -> FilePath -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ FilePath
"Invalid media type literal " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
Text.unpack Text
str) MediaType -> Parser MediaType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe MediaType -> Parser MediaType)
-> Maybe MediaType -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe MediaType
forall a. Accept a => ByteString -> Maybe a
parseAccept (ByteString -> Maybe MediaType) -> ByteString -> Maybe MediaType
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
str

instance FromJSONKey MediaType where
  fromJSONKey :: FromJSONKeyFunction MediaType
fromJSONKey = (Text -> Parser MediaType) -> FromJSONKeyFunction MediaType
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser (Value -> Parser MediaType
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser MediaType)
-> (Text -> Value) -> Text -> Parser MediaType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
String)

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

instance FromJSON OAuth2Flows where
  parseJSON :: Value -> Parser OAuth2Flows
parseJSON = Value -> Parser OAuth2Flows
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 Object
o) = do
    (Text
t :: Text) <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type"
    case Text
t of
      Text
"http"   -> do
          Text
scheme <-  Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"scheme"
          HttpSchemeType -> SecuritySchemeType
SecuritySchemeHttp (HttpSchemeType -> SecuritySchemeType)
-> Parser HttpSchemeType -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Text
scheme of
              Text
"bearer" -> Maybe Text -> HttpSchemeType
HttpSchemeBearer (Maybe Text -> HttpSchemeType)
-> Parser (Maybe Text) -> Parser HttpSchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:! Text
"bearerFormat")
              Text
"basic" -> HttpSchemeType -> Parser HttpSchemeType
forall (f :: * -> *) a. Applicative f => a -> f a
pure HttpSchemeType
HttpSchemeBasic
              Text
t -> HttpSchemeType -> Parser HttpSchemeType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HttpSchemeType -> Parser HttpSchemeType)
-> HttpSchemeType -> Parser HttpSchemeType
forall a b. (a -> b) -> a -> b
$ Text -> HttpSchemeType
HttpSchemeCustom Text
t
      Text
"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
      Text
"oauth2" -> OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Flows -> SecuritySchemeType)
-> Parser OAuth2Flows -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Text -> Parser OAuth2Flows
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"flows")
      Text
"openIdConnect" -> URL -> SecuritySchemeType
SecuritySchemeOpenIdConnect (URL -> SecuritySchemeType)
-> Parser URL -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Text -> Parser URL
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"openIdConnectUrl")
      Text
_ -> Parser SecuritySchemeType
forall (f :: * -> *) a. Alternative f => f a
empty
  parseJSON Value
_ = Parser SecuritySchemeType
forall (f :: * -> *) a. Alternative f => f a
empty

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

instance FromJSON Server where
  parseJSON :: Value -> Parser Server
parseJSON = Value -> Parser Server
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 Schema
s =
            if Schema -> Maybe OpenApiItems
_schemaItems Schema
s Maybe OpenApiItems -> Maybe OpenApiItems -> Bool
forall a. Eq a => a -> a -> Bool
== OpenApiItems -> Maybe OpenApiItems
forall a. a -> Maybe a
Just ([Referenced Schema] -> OpenApiItems
OpenApiItemsArray [])
              then Schema
s { _schemaExample :: Maybe Value
_schemaExample = Maybe Value
forall a. Maybe a
Nothing
                     , _schemaMaxItems :: Maybe Integer
_schemaMaxItems = 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 OpenApiItems where
  parseJSON :: Value -> Parser OpenApiItems
parseJSON js :: Value
js@(Object Object
obj)
      | Object -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Object
obj  = OpenApiItems -> Parser OpenApiItems
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OpenApiItems -> Parser OpenApiItems)
-> OpenApiItems -> Parser OpenApiItems
forall a b. (a -> b) -> a -> b
$ [Referenced Schema] -> OpenApiItems
OpenApiItemsArray [] -- Nullary schema.
      | Bool
otherwise = Referenced Schema -> OpenApiItems
OpenApiItemsObject (Referenced Schema -> OpenApiItems)
-> Parser (Referenced Schema) -> Parser OpenApiItems
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 Array
_)  = [Referenced Schema] -> OpenApiItems
OpenApiItemsArray  ([Referenced Schema] -> OpenApiItems)
-> Parser [Referenced Schema] -> Parser OpenApiItems
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 Value
_ = Parser OpenApiItems
forall (f :: * -> *) a. Alternative f => f a
empty

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

instance FromJSON MimeList where
  parseJSON :: Value -> Parser MimeList
parseJSON 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 Responses where
  parseJSON :: Value -> Parser Responses
parseJSON (Object 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 -> Text -> Parser (Maybe (Referenced Response))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"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 (Text -> Object -> Object
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HashMap.delete Text
"default" Object
o))
  parseJSON Value
_ = Parser Responses
forall (f :: * -> *) a. Alternative f => f a
empty

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

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 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 RequestBody where
  parseJSON :: Value -> Parser RequestBody
parseJSON = Value -> Parser RequestBody
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
 All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON

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

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

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

instance FromJSON Reference where
  parseJSON :: Value -> Parser Reference
parseJSON (Object 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 -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"$ref"
  parseJSON Value
_ = 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 Text
prefix js :: Value
js@(Object Object
o) = do
  Maybe Text
ms <- Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"$ref"
  case Maybe Text
ms of
    Maybe Text
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 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 Text
s = do
      case Text -> Text -> Maybe Text
Text.stripPrefix Text
prefix Text
s of
        Maybe Text
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
$ FilePath
"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
<> FilePath
"*\", but got " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
forall a. Show a => a -> FilePath
show Text
s
        Just Text
suffix -> Reference -> Parser Reference
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Reference
Reference Text
suffix)
referencedParseJSON Text
_ Value
_ = FilePath -> Parser (Referenced a)
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"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 Text
"#/components/schemas/"
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 Text
"#/components/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 Text
"#/components/responses/"
instance FromJSON (Referenced RequestBody) where parseJSON :: Value -> Parser (Referenced RequestBody)
parseJSON = Text -> Value -> Parser (Referenced RequestBody)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/requestBodies/"
instance FromJSON (Referenced Example)  where parseJSON :: Value -> Parser (Referenced Example)
parseJSON = Text -> Value -> Parser (Referenced Example)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/examples/"
instance FromJSON (Referenced Header)   where parseJSON :: Value -> Parser (Referenced Header)
parseJSON = Text -> Value -> Parser (Referenced Header)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/headers/"
instance FromJSON (Referenced Link)     where parseJSON :: Value -> Parser (Referenced Link)
parseJSON = Text -> Value -> Parser (Referenced Link)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/links/"
instance FromJSON (Referenced Callback) where parseJSON :: Value -> Parser (Referenced Callback)
parseJSON = Text -> Value -> Parser (Referenced Callback)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/callbacks/"

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 FilePath
"xml")

instance FromJSON AdditionalProperties where
  parseJSON :: Value -> Parser AdditionalProperties
parseJSON (Bool 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 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

-- | All strings are parsed as expressions
instance FromJSON ExpressionOrValue where
  parseJSON :: Value -> Parser ExpressionOrValue
parseJSON (String Text
expr) = ExpressionOrValue -> Parser ExpressionOrValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpressionOrValue -> Parser ExpressionOrValue)
-> ExpressionOrValue -> Parser ExpressionOrValue
forall a b. (a -> b) -> a -> b
$ Text -> ExpressionOrValue
Expression Text
expr
  parseJSON Value
v = ExpressionOrValue -> Parser ExpressionOrValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpressionOrValue -> Parser ExpressionOrValue)
-> ExpressionOrValue -> Parser ExpressionOrValue
forall a b. (a -> b) -> a -> b
$ Value -> ExpressionOrValue
Value Value
v

instance FromJSON Callback where
  parseJSON :: Value -> Parser Callback
parseJSON = (InsOrdHashMap Text PathItem -> Callback)
-> Parser (InsOrdHashMap Text PathItem) -> Parser Callback
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InsOrdHashMap Text PathItem -> Callback
Callback (Parser (InsOrdHashMap Text PathItem) -> Parser Callback)
-> (Value -> Parser (InsOrdHashMap Text PathItem))
-> Value
-> Parser Callback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (InsOrdHashMap Text PathItem)
forall a. FromJSON a => Value -> Parser a
parseJSON

instance HasSwaggerAesonOptions Server where
  swaggerAesonOptions :: Proxy Server -> SwaggerAesonOptions
swaggerAesonOptions Proxy Server
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"server"
instance HasSwaggerAesonOptions Components where
  swaggerAesonOptions :: Proxy Components -> SwaggerAesonOptions
swaggerAesonOptions Proxy Components
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"components"
instance HasSwaggerAesonOptions Header where
  swaggerAesonOptions :: Proxy Header -> SwaggerAesonOptions
swaggerAesonOptions Proxy Header
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"header"
instance AesonDefaultValue p => HasSwaggerAesonOptions (OAuth2Flow p) where
  swaggerAesonOptions :: Proxy (OAuth2Flow p) -> SwaggerAesonOptions
swaggerAesonOptions Proxy (OAuth2Flow p)
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"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
?~ FilePath
"params"
instance HasSwaggerAesonOptions OAuth2Flows where
  swaggerAesonOptions :: Proxy OAuth2Flows -> SwaggerAesonOptions
swaggerAesonOptions Proxy OAuth2Flows
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"oauth2Flows"
instance HasSwaggerAesonOptions Operation where
  swaggerAesonOptions :: Proxy Operation -> SwaggerAesonOptions
swaggerAesonOptions Proxy Operation
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"operation"
instance HasSwaggerAesonOptions Param where
  swaggerAesonOptions :: Proxy Param -> SwaggerAesonOptions
swaggerAesonOptions Proxy Param
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"param"
instance HasSwaggerAesonOptions PathItem where
  swaggerAesonOptions :: Proxy PathItem -> SwaggerAesonOptions
swaggerAesonOptions Proxy PathItem
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"pathItem"
instance HasSwaggerAesonOptions Response where
  swaggerAesonOptions :: Proxy Response -> SwaggerAesonOptions
swaggerAesonOptions Proxy Response
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"response"
instance HasSwaggerAesonOptions RequestBody where
  swaggerAesonOptions :: Proxy RequestBody -> SwaggerAesonOptions
swaggerAesonOptions Proxy RequestBody
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"requestBody"
instance HasSwaggerAesonOptions MediaTypeObject where
  swaggerAesonOptions :: Proxy MediaTypeObject -> SwaggerAesonOptions
swaggerAesonOptions Proxy MediaTypeObject
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"mediaTypeObject"
instance HasSwaggerAesonOptions Responses where
  swaggerAesonOptions :: Proxy Responses -> SwaggerAesonOptions
swaggerAesonOptions Proxy Responses
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"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
?~ FilePath
"responses"
instance HasSwaggerAesonOptions SecurityScheme where
  swaggerAesonOptions :: Proxy SecurityScheme -> SwaggerAesonOptions
swaggerAesonOptions Proxy SecurityScheme
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"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
?~ FilePath
"type"
instance HasSwaggerAesonOptions Schema where
  swaggerAesonOptions :: Proxy Schema -> SwaggerAesonOptions
swaggerAesonOptions Proxy Schema
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"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
?~ FilePath
"paramSchema"
instance HasSwaggerAesonOptions OpenApi where
  swaggerAesonOptions :: Proxy OpenApi -> SwaggerAesonOptions
swaggerAesonOptions Proxy OpenApi
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"swagger" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& ([Pair] -> Identity [Pair])
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions [Pair]
saoAdditionalPairs (([Pair] -> Identity [Pair])
 -> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> [Pair] -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [(Text
"openapi", Value
"3.0.0")]
instance HasSwaggerAesonOptions Example where
  swaggerAesonOptions :: Proxy Example -> SwaggerAesonOptions
swaggerAesonOptions Proxy Example
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"example"
instance HasSwaggerAesonOptions Encoding where
  swaggerAesonOptions :: Proxy Encoding -> SwaggerAesonOptions
swaggerAesonOptions Proxy Encoding
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"encoding"

instance HasSwaggerAesonOptions Link where
  swaggerAesonOptions :: Proxy Link -> SwaggerAesonOptions
swaggerAesonOptions Proxy Link
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"link"

instance AesonDefaultValue Server
instance AesonDefaultValue Components
instance AesonDefaultValue OAuth2ImplicitFlow
instance AesonDefaultValue OAuth2PasswordFlow
instance AesonDefaultValue OAuth2ClientCredentialsFlow
instance AesonDefaultValue OAuth2AuthorizationCodeFlow
instance AesonDefaultValue p => AesonDefaultValue (OAuth2Flow p)
instance AesonDefaultValue Responses
instance AesonDefaultValue SecuritySchemeType
instance AesonDefaultValue OpenApiType
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 Link