{-# LANGUAGE CPP #-}
{-# 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)
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.KeyMap as KeyMap
#endif
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 Text.Read (readMaybe)
import Data.HashMap.Strict.InsOrd (InsOrdHashMap)
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
import Data.OpenApi.Aeson.Compat (deleteKey)
import Data.OpenApi.Internal.AesonUtils (AesonDefaultValue (..), HasSwaggerAesonOptions (..),
mkSwaggerAesonOptions, saoAdditionalPairs, saoSubObject,
sopSwaggerGenericParseJSON, sopSwaggerGenericToEncoding,
sopSwaggerGenericToJSON, sopSwaggerGenericToJSONWithOpts)
import Data.OpenApi.Internal.Utils
import Generics.SOP.TH (deriveGeneric)
import Data.Version
import Control.Monad (unless)
import Text.ParserCombinators.ReadP (readP_to_S)
type Definitions = InsOrdHashMap Text
data OpenApi = OpenApi
{
OpenApi -> Info
_openApiInfo :: Info
, OpenApi -> [Server]
_openApiServers :: [Server]
, OpenApi -> InsOrdHashMap FilePath PathItem
_openApiPaths :: InsOrdHashMap FilePath PathItem
, OpenApi -> Components
_openApiComponents :: Components
, OpenApi -> [SecurityRequirement]
_openApiSecurity :: [SecurityRequirement]
, OpenApi -> InsOrdHashSet Tag
_openApiTags :: InsOrdHashSet Tag
, OpenApi -> Maybe ExternalDocs
_openApiExternalDocs :: Maybe ExternalDocs
,
OpenApi -> OpenApiSpecVersion
_openApiOpenapi :: OpenApiSpecVersion
} deriving (OpenApi -> OpenApi -> Bool
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
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. 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
OpenApi -> DataType
OpenApi -> Constr
(forall b. Data b => b -> b) -> OpenApi -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApi -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApi -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApi -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApi -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
lowerOpenApiSpecVersion :: Version
lowerOpenApiSpecVersion :: Version
lowerOpenApiSpecVersion = [Int] -> Version
makeVersion [Int
3, Int
0, Int
0]
upperOpenApiSpecVersion :: Version
upperOpenApiSpecVersion :: Version
upperOpenApiSpecVersion = [Int] -> Version
makeVersion [Int
3, Int
0, Int
3]
data Info = Info
{
Info -> TagName
_infoTitle :: Text
, Info -> Maybe TagName
_infoDescription :: Maybe Text
, Info -> Maybe TagName
_infoTermsOfService :: Maybe Text
, Info -> Maybe Contact
_infoContact :: Maybe Contact
, Info -> Maybe License
_infoLicense :: Maybe License
, Info -> TagName
_infoVersion :: Text
} deriving (Info -> Info -> Bool
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
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. 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
Info -> DataType
Info -> Constr
(forall b. Data b => b -> b) -> Info -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Info -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Info -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Contact = Contact
{
Contact -> Maybe TagName
_contactName :: Maybe Text
, Contact -> Maybe URL
_contactUrl :: Maybe URL
, Contact -> Maybe TagName
_contactEmail :: Maybe Text
} deriving (Contact -> Contact -> Bool
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
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. 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
Contact -> DataType
Contact -> Constr
(forall b. Data b => b -> b) -> Contact -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Contact -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Contact -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data License = License
{
License -> TagName
_licenseName :: Text
, License -> Maybe URL
_licenseUrl :: Maybe URL
} deriving (License -> License -> Bool
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
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. 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
License -> DataType
License -> Constr
(forall b. Data b => b -> b) -> License -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance IsString License where
fromString :: FilePath -> License
fromString FilePath
s = TagName -> Maybe URL -> License
License (forall a. IsString a => FilePath -> a
fromString FilePath
s) forall a. Maybe a
Nothing
data Server = Server
{
Server -> TagName
_serverUrl :: Text
, Server -> Maybe TagName
_serverDescription :: Maybe Text
, Server -> InsOrdHashMap TagName ServerVariable
_serverVariables :: InsOrdHashMap Text ServerVariable
} deriving (Server -> Server -> Bool
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
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. 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
Server -> DataType
Server -> Constr
(forall b. Data b => b -> b) -> Server -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Server -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Server -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Server -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Server -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data ServerVariable = ServerVariable
{
ServerVariable -> Maybe (InsOrdHashSet TagName)
_serverVariableEnum :: Maybe (InsOrdHashSet Text)
, ServerVariable -> TagName
_serverVariableDefault :: Text
, ServerVariable -> Maybe TagName
_serverVariableDescription :: Maybe Text
} deriving (ServerVariable -> ServerVariable -> Bool
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
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. 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
ServerVariable -> DataType
ServerVariable -> Constr
(forall b. Data b => b -> b) -> ServerVariable -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance IsString Server where
fromString :: FilePath -> Server
fromString FilePath
s = TagName
-> Maybe TagName -> InsOrdHashMap TagName ServerVariable -> Server
Server (forall a. IsString a => FilePath -> a
fromString FilePath
s) forall a. Maybe a
Nothing forall a. Monoid a => a
mempty
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
, :: Definitions Header
, Components -> SecurityDefinitions
_componentsSecuritySchemes :: SecurityDefinitions
, Components -> Definitions Link
_componentsLinks :: Definitions Link
, Components -> Definitions Callback
_componentsCallbacks :: Definitions Callback
} deriving (Components -> Components -> Bool
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
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. 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
Components -> DataType
Components -> Constr
(forall b. Data b => b -> b) -> Components -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Components -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Components -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Components -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Components -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data PathItem = PathItem
{
PathItem -> Maybe TagName
_pathItemSummary :: Maybe Text
, PathItem -> Maybe TagName
_pathItemDescription :: Maybe Text
, PathItem -> Maybe Operation
_pathItemGet :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemPut :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemPost :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemDelete :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemOptions :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemHead :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemPatch :: Maybe Operation
, PathItem -> Maybe Operation
_pathItemTrace :: Maybe Operation
, PathItem -> [Server]
_pathItemServers :: [Server]
, PathItem -> [Referenced Param]
_pathItemParameters :: [Referenced Param]
} deriving (PathItem -> PathItem -> Bool
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
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. 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
PathItem -> DataType
PathItem -> Constr
(forall b. Data b => b -> b) -> PathItem -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Operation = Operation
{
Operation -> InsOrdHashSet TagName
_operationTags :: InsOrdHashSet TagName
, Operation -> Maybe TagName
_operationSummary :: Maybe Text
, Operation -> Maybe TagName
_operationDescription :: Maybe Text
, Operation -> Maybe ExternalDocs
_operationExternalDocs :: Maybe ExternalDocs
, Operation -> Maybe TagName
_operationOperationId :: Maybe Text
, Operation -> [Referenced Param]
_operationParameters :: [Referenced Param]
, Operation -> Maybe (Referenced RequestBody)
_operationRequestBody :: Maybe (Referenced RequestBody)
, Operation -> Responses
_operationResponses :: Responses
, Operation -> InsOrdHashMap TagName (Referenced Callback)
_operationCallbacks :: InsOrdHashMap Text (Referenced Callback)
, Operation -> Maybe Bool
_operationDeprecated :: Maybe Bool
, Operation -> [SecurityRequirement]
_operationSecurity :: [SecurityRequirement]
, Operation -> [Server]
_operationServers :: [Server]
} deriving (Operation -> Operation -> Bool
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
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. 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
Operation -> DataType
Operation -> Constr
(forall b. Data b => b -> b) -> Operation -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Operation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Operation -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance Data MediaType where
gunfold :: forall (c :: * -> *).
(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 -> forall b r. Data b => c (b -> r) -> c r
k (forall b r. Data b => c (b -> r) -> c r
k (forall b r. Data b => c (b -> r) -> c r
k (forall r. r -> c r
z (\ByteString
main ByteString
sub Map ByteString ByteString
params -> 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) (forall k a. Map k a -> [(k, a)]
Map.toList Map ByteString ByteString
params)))))
Int
_ -> forall a. HasCallStack => FilePath -> a
error forall a b. (a -> b) -> a -> b
$ FilePath
"Data.Data.gunfold: Constructor " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Constr
c 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 forall a. Hashable a => Int -> a -> Int
`hashWithSalt` forall a. Show a => a -> FilePath
show MediaType
mt
data RequestBody = RequestBody
{
RequestBody -> Maybe TagName
_requestBodyDescription :: Maybe Text
, RequestBody -> InsOrdHashMap MediaType MediaTypeObject
_requestBodyContent :: InsOrdHashMap MediaType MediaTypeObject
, RequestBody -> Maybe Bool
_requestBodyRequired :: Maybe Bool
} deriving (RequestBody -> RequestBody -> Bool
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
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. 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
RequestBody -> DataType
RequestBody -> Constr
(forall b. Data b => b -> b) -> RequestBody -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> RequestBody -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RequestBody -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RequestBody -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RequestBody -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data MediaTypeObject = MediaTypeObject
{ MediaTypeObject -> Maybe (Referenced Schema)
_mediaTypeObjectSchema :: Maybe (Referenced Schema)
, MediaTypeObject -> Maybe Value
_mediaTypeObjectExample :: Maybe Value
, MediaTypeObject -> InsOrdHashMap TagName (Referenced Example)
_mediaTypeObjectExamples :: InsOrdHashMap Text (Referenced Example)
, MediaTypeObject -> InsOrdHashMap TagName Encoding
_mediaTypeObjectEncoding :: InsOrdHashMap Text Encoding
} deriving (MediaTypeObject -> MediaTypeObject -> Bool
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
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. 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
MediaTypeObject -> DataType
MediaTypeObject -> Constr
(forall b. Data b => b -> b) -> MediaTypeObject -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Style
= StyleMatrix
| StyleLabel
| StyleForm
| StyleSimple
| StyleSpaceDelimited
| StylePipeDelimited
| StyleDeepObject
deriving (Style -> Style -> Bool
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
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. 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
Style -> DataType
Style -> Constr
(forall b. Data b => b -> b) -> Style -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Encoding = Encoding
{
Encoding -> Maybe MediaType
_encodingContentType :: Maybe MediaType
, :: InsOrdHashMap Text (Referenced Header)
, Encoding -> Maybe Style
_encodingStyle :: Maybe Style
, Encoding -> Maybe Bool
_encodingExplode :: Maybe Bool
, Encoding -> Maybe Bool
_encodingAllowReserved :: Maybe Bool
} deriving (Encoding -> Encoding -> Bool
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
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. 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
Encoding -> DataType
Encoding -> Constr
(forall b. Data b => b -> b) -> Encoding -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype MimeList = MimeList { MimeList -> [MediaType]
getMimeList :: [MediaType] }
deriving (MimeList -> MimeList -> Bool
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
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, NonEmpty MimeList -> MimeList
MimeList -> MimeList -> 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 :: forall b. Integral b => 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
[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
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 (c :: * -> *).
(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 -> forall b r. Data b => c (b -> r) -> c r
k (forall r. r -> c r
z ([MediaType] -> MimeList
MimeList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. IsString a => FilePath -> a
fromString))
Int
_ -> forall a. HasCallStack => FilePath -> a
error forall a b. (a -> b) -> a -> b
$ FilePath
"Data.Data.gunfold: Constructor " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Constr
c 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
data Param = Param
{
Param -> TagName
_paramName :: Text
, Param -> Maybe TagName
_paramDescription :: Maybe Text
, Param -> Maybe Bool
_paramRequired :: Maybe Bool
, Param -> Maybe Bool
_paramDeprecated :: Maybe Bool
, Param -> ParamLocation
_paramIn :: ParamLocation
, Param -> Maybe Bool
_paramAllowEmptyValue :: Maybe Bool
, Param -> Maybe Bool
_paramAllowReserved :: Maybe Bool
, Param -> Maybe (Referenced Schema)
_paramSchema :: Maybe (Referenced Schema)
, Param -> Maybe Style
_paramStyle :: Maybe Style
, Param -> Maybe Bool
_paramExplode :: Maybe Bool
, Param -> Maybe Value
_paramExample :: Maybe Value
, Param -> InsOrdHashMap TagName (Referenced Example)
_paramExamples :: InsOrdHashMap Text (Referenced Example)
} deriving (Param -> Param -> Bool
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
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. 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
Param -> DataType
Param -> Constr
(forall b. Data b => b -> b) -> Param -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Param -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Param -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Example = Example
{
Example -> Maybe TagName
_exampleSummary :: Maybe Text
, Example -> Maybe TagName
_exampleDescription :: Maybe Text
, Example -> Maybe Value
_exampleValue :: Maybe Value
, Example -> Maybe URL
_exampleExternalValue :: Maybe URL
} deriving (Example -> Example -> Bool
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
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. 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
Example -> DataType
Example -> Constr
(forall b. Data b => b -> b) -> Example -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Example -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Example -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Example -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Example -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data)
data ExpressionOrValue
= Expression Text
| Value Value
deriving (ExpressionOrValue -> ExpressionOrValue -> Bool
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
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. 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
ExpressionOrValue -> DataType
ExpressionOrValue -> Constr
(forall b. Data b => b -> b)
-> ExpressionOrValue -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> ExpressionOrValue -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExpressionOrValue -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExpressionOrValue -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExpressionOrValue -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data)
data Link = Link
{
Link -> Maybe TagName
_linkOperationRef :: Maybe Text
, Link -> Maybe TagName
_linkOperationId :: Maybe Text
, Link -> InsOrdHashMap TagName ExpressionOrValue
_linkParameters :: InsOrdHashMap Text ExpressionOrValue
, Link -> Maybe ExpressionOrValue
_linkRequestBody :: Maybe ExpressionOrValue
, Link -> Maybe TagName
_linkDescription :: Maybe Text
, Link -> Maybe Server
_linkServer :: Maybe Server
} deriving (Link -> Link -> Bool
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
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. 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
Link -> DataType
Link -> Constr
(forall b. Data b => b -> b) -> Link -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data)
data OpenApiItems where
OpenApiItemsObject :: Referenced Schema -> OpenApiItems
OpenApiItemsArray :: [Referenced Schema] -> OpenApiItems
deriving (OpenApiItems -> OpenApiItems -> Bool
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
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
OpenApiItems -> DataType
OpenApiItems -> Constr
(forall b. Data b => b -> b) -> OpenApiItems -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data)
data OpenApiType where
OpenApiString :: OpenApiType
OpenApiNumber :: OpenApiType
OpenApiInteger :: OpenApiType
OpenApiBoolean :: OpenApiType
OpenApiArray :: OpenApiType
OpenApiNull :: OpenApiType
OpenApiObject :: OpenApiType
deriving (OpenApiType -> OpenApiType -> Bool
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
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. 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
OpenApiType -> DataType
OpenApiType -> Constr
(forall b. Data b => b -> b) -> OpenApiType -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data)
data ParamLocation
=
ParamQuery
|
| ParamPath
| ParamCookie
deriving (ParamLocation -> ParamLocation -> Bool
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
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. 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
ParamLocation -> DataType
ParamLocation -> Constr
(forall b. Data b => b -> b) -> ParamLocation -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type Format = Text
type ParamName = Text
data Schema = Schema
{ Schema -> Maybe TagName
_schemaTitle :: Maybe Text
, Schema -> Maybe TagName
_schemaDescription :: Maybe Text
, Schema -> [TagName]
_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 TagName (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
,
Schema -> Maybe Value
_schemaDefault :: Maybe Value
, Schema -> Maybe OpenApiType
_schemaType :: Maybe OpenApiType
, Schema -> Maybe TagName
_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 TagName
_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
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
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. 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
Schema -> DataType
Schema -> Constr
(forall b. Data b => b -> b) -> Schema -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Schema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Schema -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type Pattern = Text
data Discriminator = Discriminator
{
Discriminator -> TagName
_discriminatorPropertyName :: Text
, Discriminator -> InsOrdHashMap TagName TagName
_discriminatorMapping :: InsOrdHashMap Text Text
} deriving (Discriminator -> Discriminator -> Bool
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
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. 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
Discriminator -> DataType
Discriminator -> Constr
(forall b. Data b => b -> b) -> Discriminator -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Discriminator -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Discriminator -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data NamedSchema = NamedSchema
{ NamedSchema -> Maybe TagName
_namedSchemaName :: Maybe Text
, NamedSchema -> Schema
_namedSchemaSchema :: Schema
} deriving (NamedSchema -> NamedSchema -> Bool
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
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. 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
NamedSchema -> DataType
NamedSchema -> Constr
(forall b. Data b => b -> b) -> NamedSchema -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Xml = Xml
{
Xml -> Maybe TagName
_xmlName :: Maybe Text
, Xml -> Maybe TagName
_xmlNamespace :: Maybe Text
, Xml -> Maybe TagName
_xmlPrefix :: Maybe Text
, Xml -> Maybe Bool
_xmlAttribute :: Maybe Bool
, Xml -> Maybe Bool
_xmlWrapped :: Maybe Bool
} deriving (Xml -> Xml -> Bool
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
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. 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
Xml -> DataType
Xml -> Constr
(forall b. Data b => b -> b) -> Xml -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Xml -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Xml -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Responses = Responses
{
Responses -> Maybe (Referenced Response)
_responsesDefault :: Maybe (Referenced Response)
, Responses -> InsOrdHashMap Int (Referenced Response)
_responsesResponses :: InsOrdHashMap HttpStatusCode (Referenced Response)
} deriving (Responses -> Responses -> Bool
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
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. 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
Responses -> DataType
Responses -> Constr
(forall b. Data b => b -> b) -> Responses -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Responses -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Responses -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type HttpStatusCode = Int
data Response = Response
{
Response -> TagName
_responseDescription :: Text
, Response -> InsOrdHashMap MediaType MediaTypeObject
_responseContent :: InsOrdHashMap MediaType MediaTypeObject
, :: InsOrdHashMap HeaderName (Referenced Header)
, Response -> InsOrdHashMap TagName (Referenced Link)
_responseLinks :: InsOrdHashMap Text (Referenced Link)
} deriving (Response -> Response -> Bool
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
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. 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
Response -> DataType
Response -> Constr
(forall b. Data b => b -> b) -> Response -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Response -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Response -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance IsString Response where
fromString :: FilePath -> Response
fromString FilePath
s = TagName
-> InsOrdHashMap MediaType MediaTypeObject
-> InsOrdHashMap TagName (Referenced Header)
-> InsOrdHashMap TagName (Referenced Link)
-> Response
Response (forall a. IsString a => FilePath -> a
fromString FilePath
s) forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty
newtype Callback = Callback (InsOrdHashMap Text PathItem)
deriving (Callback -> Callback -> Bool
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
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. 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
Callback -> DataType
Callback -> Constr
(forall b. Data b => b -> b) -> Callback -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Callback -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Callback -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type = Text
data =
{
:: Maybe HeaderName
, :: Maybe Bool
, :: Maybe Bool
, :: Maybe Bool
, :: Maybe Bool
, :: Maybe Value
, :: InsOrdHashMap Text (Referenced Example)
, :: Maybe (Referenced Schema)
} deriving (Header -> Header -> Bool
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
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. 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
Header -> DataType
Header -> Constr
(forall b. Data b => b -> b) -> Header -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data ApiKeyLocation
= ApiKeyQuery
|
| ApiKeyCookie
deriving (ApiKeyLocation -> ApiKeyLocation -> Bool
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
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. 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
ApiKeyLocation -> DataType
ApiKeyLocation -> Constr
(forall b. Data b => b -> b) -> ApiKeyLocation -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data ApiKeyParams = ApiKeyParams
{
ApiKeyParams -> TagName
_apiKeyName :: Text
, ApiKeyParams -> ApiKeyLocation
_apiKeyIn :: ApiKeyLocation
} deriving (ApiKeyParams -> ApiKeyParams -> Bool
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
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. 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
ApiKeyParams -> DataType
ApiKeyParams -> Constr
(forall b. Data b => b -> b) -> ApiKeyParams -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type AuthorizationURL = Text
type TokenURL = Text
newtype OAuth2ImplicitFlow
= OAuth2ImplicitFlow {OAuth2ImplicitFlow -> TagName
_oAuth2ImplicitFlowAuthorizationUrl :: AuthorizationURL}
deriving (OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
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
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. 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
OAuth2ImplicitFlow -> DataType
OAuth2ImplicitFlow -> Constr
(forall b. Data b => b -> b)
-> OAuth2ImplicitFlow -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype OAuth2PasswordFlow
= OAuth2PasswordFlow {OAuth2PasswordFlow -> TagName
_oAuth2PasswordFlowTokenUrl :: TokenURL}
deriving (OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
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
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. 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
OAuth2PasswordFlow -> DataType
OAuth2PasswordFlow -> Constr
(forall b. Data b => b -> b)
-> OAuth2PasswordFlow -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype OAuth2ClientCredentialsFlow
= OAuth2ClientCredentialsFlow {OAuth2ClientCredentialsFlow -> TagName
_oAuth2ClientCredentialsFlowTokenUrl :: TokenURL}
deriving (OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
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
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.
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
OAuth2ClientCredentialsFlow -> DataType
OAuth2ClientCredentialsFlow -> Constr
(forall b. Data b => b -> b)
-> OAuth2ClientCredentialsFlow -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data OAuth2AuthorizationCodeFlow = OAuth2AuthorizationCodeFlow
{ OAuth2AuthorizationCodeFlow -> TagName
_oAuth2AuthorizationCodeFlowAuthorizationUrl :: AuthorizationURL
, OAuth2AuthorizationCodeFlow -> TagName
_oAuth2AuthorizationCodeFlowTokenUrl :: TokenURL
} deriving (OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
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
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.
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
OAuth2AuthorizationCodeFlow -> DataType
OAuth2AuthorizationCodeFlow -> Constr
(forall b. Data b => b -> b)
-> OAuth2AuthorizationCodeFlow -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data OAuth2Flow p = OAuth2Flow
{ forall p. OAuth2Flow p -> p
_oAuth2Params :: p
, forall p. OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl :: Maybe URL
, forall p. OAuth2Flow p -> InsOrdHashMap TagName TagName
_oAuth2Scopes :: InsOrdHashMap Text Text
} deriving (OAuth2Flow p -> OAuth2Flow p -> Bool
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
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 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, OAuth2Flow p -> DataType
OAuth2Flow p -> Constr
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 (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))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. 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 u. (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 :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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)
Data, Typeable)
data OAuth2Flows = OAuth2Flows
{
OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit :: Maybe (OAuth2Flow OAuth2ImplicitFlow)
, OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword :: Maybe (OAuth2Flow OAuth2PasswordFlow)
, OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials :: Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
, OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode :: Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
} deriving (OAuth2Flows -> OAuth2Flows -> Bool
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
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. 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
OAuth2Flows -> DataType
OAuth2Flows -> Constr
(forall b. Data b => b -> b) -> OAuth2Flows -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flows -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flows -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Flows -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Flows -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type BearerFormat = Text
data HttpSchemeType
= HttpSchemeBearer (Maybe BearerFormat)
| HttpSchemeBasic
| HttpSchemeCustom Text
deriving (HttpSchemeType -> HttpSchemeType -> Bool
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
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. 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
HttpSchemeType -> DataType
HttpSchemeType -> Constr
(forall b. Data b => b -> b) -> HttpSchemeType -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> HttpSchemeType -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HttpSchemeType -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> HttpSchemeType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HttpSchemeType -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data SecuritySchemeType
= SecuritySchemeHttp HttpSchemeType
| SecuritySchemeApiKey ApiKeyParams
| SecuritySchemeOAuth2 OAuth2Flows
| SecuritySchemeOpenIdConnect URL
deriving (SecuritySchemeType -> SecuritySchemeType -> Bool
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
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. 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
SecuritySchemeType -> DataType
SecuritySchemeType -> Constr
(forall b. Data b => b -> b)
-> SecuritySchemeType -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data SecurityScheme = SecurityScheme
{
SecurityScheme -> SecuritySchemeType
_securitySchemeType :: SecuritySchemeType
, SecurityScheme -> Maybe TagName
_securitySchemeDescription :: Maybe Text
} deriving (SecurityScheme -> SecurityScheme -> Bool
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
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. 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
SecurityScheme -> DataType
SecurityScheme -> Constr
(forall b. Data b => b -> b) -> SecurityScheme -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype SecurityDefinitions
= SecurityDefinitions (Definitions SecurityScheme)
deriving (SecurityDefinitions -> SecurityDefinitions -> Bool
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
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. 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
SecurityDefinitions -> DataType
SecurityDefinitions -> Constr
(forall b. Data b => b -> b)
-> SecurityDefinitions -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype SecurityRequirement = SecurityRequirement
{ SecurityRequirement -> InsOrdHashMap TagName [TagName]
getSecurityRequirement :: InsOrdHashMap Text [Text]
} deriving (SecurityRequirement -> SecurityRequirement -> Bool
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]
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
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, NonEmpty SecurityRequirement -> SecurityRequirement
SecurityRequirement -> SecurityRequirement -> 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 :: forall b.
Integral b =>
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
[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
Monoid, [SecurityRequirement] -> Encoding
[SecurityRequirement] -> Value
SecurityRequirement -> Encoding
SecurityRequirement -> Value
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
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
SecurityRequirement -> DataType
SecurityRequirement -> Constr
(forall b. Data b => b -> b)
-> SecurityRequirement -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
type TagName = Text
data Tag = Tag
{
Tag -> TagName
_tagName :: TagName
, Tag -> Maybe TagName
_tagDescription :: Maybe Text
, Tag -> Maybe ExternalDocs
_tagExternalDocs :: Maybe ExternalDocs
} deriving (Tag -> Tag -> Bool
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
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
Ord, Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> FilePath
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. 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
Tag -> DataType
Tag -> Constr
(forall b. Data b => b -> b) -> Tag -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance Hashable Tag
instance IsString Tag where
fromString :: FilePath -> Tag
fromString FilePath
s = TagName -> Maybe TagName -> Maybe ExternalDocs -> Tag
Tag (forall a. IsString a => FilePath -> a
fromString FilePath
s) forall a. Maybe a
Nothing forall a. Maybe a
Nothing
data ExternalDocs = ExternalDocs
{
ExternalDocs -> Maybe TagName
_externalDocsDescription :: Maybe Text
, ExternalDocs -> URL
_externalDocsUrl :: URL
} deriving (ExternalDocs -> ExternalDocs -> Bool
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
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
Ord, Int -> ExternalDocs -> ShowS
[ExternalDocs] -> ShowS
ExternalDocs -> FilePath
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. 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
ExternalDocs -> DataType
ExternalDocs -> Constr
(forall b. Data b => b -> b) -> ExternalDocs -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
instance Hashable ExternalDocs
newtype Reference = Reference { Reference -> TagName
getReference :: Text }
deriving (Reference -> Reference -> Bool
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
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
Reference -> DataType
Reference -> Constr
(forall b. Data b => b -> b) -> Reference -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Reference -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Reference -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data Referenced a
= Ref Reference
| Inline a
deriving (Referenced a -> Referenced a -> Bool
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
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, 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
<$ :: forall a b. a -> Referenced b -> Referenced a
$c<$ :: forall a b. a -> Referenced b -> Referenced a
fmap :: forall a b. (a -> b) -> Referenced a -> Referenced b
$cfmap :: forall a b. (a -> b) -> Referenced a -> Referenced b
Functor, Referenced a -> DataType
Referenced a -> Constr
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 (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))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. 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 u. (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 :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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)
Data, Typeable)
instance IsString a => IsString (Referenced a) where
fromString :: FilePath -> Referenced a
fromString = forall a. a -> Referenced a
Inline forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString
newtype URL = URL { URL -> TagName
getUrl :: Text } deriving (URL -> URL -> Bool
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
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
Ord, Int -> URL -> ShowS
[URL] -> ShowS
URL -> FilePath
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, Eq URL
Int -> URL -> Int
URL -> Int
forall a. Eq 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
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
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
URL -> DataType
URL -> Constr
(forall b. Data b => b -> b) -> URL -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> URL -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> URL -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
data AdditionalProperties
= AdditionalPropertiesAllowed Bool
| AdditionalPropertiesSchema (Referenced Schema)
deriving (AdditionalProperties -> AdditionalProperties -> Bool
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
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
AdditionalProperties -> DataType
AdditionalProperties -> Constr
(forall b. Data b => b -> b)
-> AdditionalProperties -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable)
newtype OpenApiSpecVersion = OpenApiSpecVersion {OpenApiSpecVersion -> Version
getVersion :: Version} deriving (OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
$c/= :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
== :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
$c== :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
Eq, Int -> OpenApiSpecVersion -> ShowS
[OpenApiSpecVersion] -> ShowS
OpenApiSpecVersion -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OpenApiSpecVersion] -> ShowS
$cshowList :: [OpenApiSpecVersion] -> ShowS
show :: OpenApiSpecVersion -> FilePath
$cshow :: OpenApiSpecVersion -> FilePath
showsPrec :: Int -> OpenApiSpecVersion -> ShowS
$cshowsPrec :: Int -> OpenApiSpecVersion -> ShowS
Show, forall x. Rep OpenApiSpecVersion x -> OpenApiSpecVersion
forall x. OpenApiSpecVersion -> Rep OpenApiSpecVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenApiSpecVersion x -> OpenApiSpecVersion
$cfrom :: forall x. OpenApiSpecVersion -> Rep OpenApiSpecVersion x
Generic, Typeable OpenApiSpecVersion
OpenApiSpecVersion -> DataType
OpenApiSpecVersion -> Constr
(forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion
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) -> OpenApiSpecVersion -> u
forall u. (forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiSpecVersion)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiSpecVersion)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiSpecVersion -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiSpecVersion -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
gmapT :: (forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion
$cgmapT :: (forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiSpecVersion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiSpecVersion)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiSpecVersion)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiSpecVersion)
dataTypeOf :: OpenApiSpecVersion -> DataType
$cdataTypeOf :: OpenApiSpecVersion -> DataType
toConstr :: OpenApiSpecVersion -> Constr
$ctoConstr :: OpenApiSpecVersion -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion
Data, Typeable)
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
deriveGeneric ''OpenApiSpecVersion
instance Semigroup OpenApiSpecVersion where
<> :: OpenApiSpecVersion -> OpenApiSpecVersion -> OpenApiSpecVersion
(<>) (OpenApiSpecVersion Version
a) (OpenApiSpecVersion Version
b) = Version -> OpenApiSpecVersion
OpenApiSpecVersion forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
max Version
a Version
b
instance Monoid OpenApiSpecVersion where
mempty :: OpenApiSpecVersion
mempty = Version -> OpenApiSpecVersion
OpenApiSpecVersion ([Int] -> Version
makeVersion [Int
3,Int
0,Int
0])
mappend :: OpenApiSpecVersion -> OpenApiSpecVersion -> OpenApiSpecVersion
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup OpenApi where
<> :: OpenApi -> OpenApi -> OpenApi
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid OpenApi where
mempty :: OpenApi
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: OpenApi -> OpenApi -> OpenApi
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Info where
<> :: Info -> Info -> Info
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Info where
mempty :: Info
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Info -> Info -> Info
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Contact where
<> :: Contact -> Contact -> Contact
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Contact where
mempty :: Contact
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Contact -> Contact -> Contact
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Components where
<> :: Components -> Components -> Components
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Components where
mempty :: Components
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Components -> Components -> Components
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup PathItem where
<> :: PathItem -> PathItem -> PathItem
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid PathItem where
mempty :: PathItem
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: PathItem -> PathItem -> PathItem
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Schema where
<> :: Schema -> Schema -> Schema
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Schema where
mempty :: Schema
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Schema -> Schema -> Schema
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Param where
<> :: Param -> Param -> Param
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Param where
mempty :: Param
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Param -> Param -> Param
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Header where
<> :: Header -> Header -> Header
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Header where
mempty :: Header
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Header -> Header -> Header
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Responses where
<> :: Responses -> Responses -> Responses
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Responses where
mempty :: Responses
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Responses -> Responses -> Responses
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Response where
<> :: Response -> Response -> Response
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Response where
mempty :: Response
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Response -> Response -> Response
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup MediaTypeObject where
<> :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid MediaTypeObject where
mempty :: MediaTypeObject
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Encoding where
<> :: Encoding -> Encoding -> Encoding
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Encoding where
mempty :: Encoding
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Encoding -> Encoding -> Encoding
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup ExternalDocs where
<> :: ExternalDocs -> ExternalDocs -> ExternalDocs
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid ExternalDocs where
mempty :: ExternalDocs
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: ExternalDocs -> ExternalDocs -> ExternalDocs
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Operation where
<> :: Operation -> Operation -> Operation
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Operation where
mempty :: Operation
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Operation -> Operation -> Operation
mappend = 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 TagName TagName
_oAuth2Scopes = InsOrdHashMap TagName TagName
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 TagName TagName
_oAuth2Scopes = InsOrdHashMap TagName TagName
rScopes } =
OAuth2Flow p
l { _oAath2RefreshUrl :: Maybe URL
_oAath2RefreshUrl = forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Maybe URL
lUrl Maybe URL
rUrl, _oAuth2Scopes :: InsOrdHashMap TagName TagName
_oAuth2Scopes = InsOrdHashMap TagName TagName
lScopes forall a. Semigroup a => a -> a -> a
<> InsOrdHashMap TagName TagName
rScopes }
instance Semigroup OAuth2Flows where
OAuth2Flows
l <> :: OAuth2Flows -> OAuth2Flows -> OAuth2Flows
<> OAuth2Flows
r = OAuth2Flows
{ _oAuth2FlowsImplicit :: Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit = OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit OAuth2Flows
l 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 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 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 forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode OAuth2Flows
r
}
instance Monoid OAuth2Flows where
mempty :: OAuth2Flows
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: OAuth2Flows -> OAuth2Flows -> OAuth2Flows
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup SecurityScheme where
SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
lFlows) Maybe TagName
lDesc
<> :: SecurityScheme -> SecurityScheme -> SecurityScheme
<> SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
rFlows) Maybe TagName
rDesc =
SecuritySchemeType -> Maybe TagName -> SecurityScheme
SecurityScheme (OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 forall a b. (a -> b) -> a -> b
$ OAuth2Flows
lFlows forall a. Semigroup a => a -> a -> a
<> OAuth2Flows
rFlows) (forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Maybe TagName
lDesc Maybe TagName
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 forall a b. (a -> b) -> a -> b
$ forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith forall a. Semigroup a => a -> a -> a
(<>) Definitions SecurityScheme
sd1 Definitions SecurityScheme
sd2
instance Monoid SecurityDefinitions where
mempty :: SecurityDefinitions
mempty = Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
mappend :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup RequestBody where
<> :: RequestBody -> RequestBody -> RequestBody
(<>) = forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid RequestBody where
mempty :: RequestBody
mempty = forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: RequestBody -> RequestBody -> RequestBody
mappend = forall a. Semigroup a => a -> a -> a
(<>)
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 SecurityDefinitions
instance SwaggerMonoid OpenApiSpecVersion
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 = forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
swaggerMappend :: InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
swaggerMappend = forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith forall a. Monoid a => a -> a -> a
mappend
instance Monoid a => SwaggerMonoid (Referenced a) where
swaggerMempty :: Referenced a
swaggerMempty = forall a. a -> Referenced a
Inline forall a. Monoid a => a
mempty
swaggerMappend :: Referenced a -> Referenced a -> Referenced a
swaggerMappend (Inline a
x) (Inline a
y) = forall a. a -> Referenced a
Inline (forall a. Monoid a => a -> a -> a
mappend a
x a
y)
swaggerMappend Referenced a
_ Referenced a
y = Referenced a
y
instance ToJSON Style where
toJSON :: Style -> Value
toJSON = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2AuthorizationCodeFlow")
instance FromJSON Style where
parseJSON :: Value -> Parser Style
parseJSON = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2AuthorizationCodeFlow")
instance ToJSON OpenApiSpecVersion where
toJSON :: OpenApiSpecVersion -> Value
toJSON (OpenApiSpecVersion Version
v)= forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> FilePath
showVersion forall a b. (a -> b) -> a -> b
$ Version
v
instance ToJSON MediaType where
toJSON :: MediaType -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> FilePath
show
toEncoding :: MediaType -> Encoding
toEncoding = forall a. ToJSON a => a -> Encoding
toEncoding forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> FilePath
show
instance ToJSONKey MediaType where
toJSONKey :: ToJSONKeyFunction MediaType
toJSONKey = forall a. (a -> TagName) -> ToJSONKeyFunction a
JSON.toJSONKeyText (FilePath -> TagName
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
a = forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON OAuth2Flow p
a forall a b. a -> (a -> b) -> b
&
if forall k v. InsOrdHashMap k v -> Bool
InsOrdHashMap.null (forall p. OAuth2Flow p -> InsOrdHashMap TagName TagName
_oAuth2Scopes OAuth2Flow p
a)
then (Value -> Value -> Value
<+> [Pair] -> Value
object [Key
"scopes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object []])
else forall a. a -> a
id
toEncoding :: OAuth2Flow p -> Encoding
toEncoding = 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 = 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 = 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 TagName
mFmt ->
[Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ [ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"http" :: Text)
, Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"bearer" :: Text)
] forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\TagName
t -> [Key
"bearerFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TagName
t]) Maybe TagName
mFmt
HttpSchemeType
HttpSchemeBasic ->
[Pair] -> Value
object [ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"http" :: Text)
, Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"basic" :: Text)
]
HttpSchemeCustom TagName
t ->
[Pair] -> Value
object [ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"http" :: Text)
, Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TagName
t
]
toJSON (SecuritySchemeApiKey ApiKeyParams
params)
= forall a. ToJSON a => a -> Value
toJSON ApiKeyParams
params
Value -> Value -> Value
<+> [Pair] -> Value
object [ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"apiKey" :: Text) ]
toJSON (SecuritySchemeOAuth2 OAuth2Flows
params) = [Pair] -> Value
object
[ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"oauth2" :: Text)
, Key
"flows" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON OAuth2Flows
params
]
toJSON (SecuritySchemeOpenIdConnect URL
url) = [Pair] -> Value
object
[ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
"openIdConnect" :: Text)
, Key
"openIdConnectUrl" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= URL
url
]
instance ToJSON OpenApi where
toJSON :: OpenApi -> Value
toJSON OpenApi
a = forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON OpenApi
a forall a b. a -> (a -> b) -> b
&
if forall k v. InsOrdHashMap k v -> Bool
InsOrdHashMap.null (OpenApi -> InsOrdHashMap FilePath PathItem
_openApiPaths OpenApi
a)
then (Value -> Value -> Value
<+> [Pair] -> Value
object [Key
"paths" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object []])
else forall a. a -> a
id
toEncoding :: OpenApi -> Encoding
toEncoding = 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 = 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 = 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 = 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 = 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 = 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 forall a b. (a -> b) -> a -> b
$
FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"schema" forall a b. a -> (a -> b) -> b
& Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"items"
instance ToJSON Header where
toJSON :: Header -> Value
toJSON = 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 = forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON OpenApiItems where
toJSON :: OpenApiItems -> Value
toJSON (OpenApiItemsObject Referenced Schema
x) = [Pair] -> Value
object [ Key
"items" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Referenced Schema
x ]
toJSON (OpenApiItemsArray []) = [Pair] -> Value
object
[ Key
"items" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object []
, Key
"maxItems" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Int
0 :: Int)
, Key
"example" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Array -> Value
Array forall a. Monoid a => a
mempty
]
toJSON (OpenApiItemsArray [Referenced Schema]
x) = [Pair] -> Value
object [ Key
"items" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Referenced Schema]
x ]
instance ToJSON Components where
toJSON :: Components -> Value
toJSON = 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 = 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) = forall a. ToJSON a => a -> Value
toJSON (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> FilePath
show [MediaType]
xs)
instance ToJSON Param where
toJSON :: Param -> Value
toJSON = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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) = forall a. ToJSON a => a -> Value
toJSON Definitions SecurityScheme
sd
instance ToJSON Reference where
toJSON :: Reference -> Value
toJSON (Reference TagName
ref) = [Pair] -> Value
object [ Key
"$ref" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TagName
ref ]
referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
referencedToJSON :: forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
prefix (Ref (Reference TagName
ref)) = [Pair] -> Value
object [ Key
"$ref" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (TagName
prefix forall a. Semigroup a => a -> a -> a
<> TagName
ref) ]
referencedToJSON TagName
_ (Inline a
x) = forall a. ToJSON a => a -> Value
toJSON a
x
instance ToJSON (Referenced Schema) where toJSON :: Referenced Schema -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/schemas/"
instance ToJSON (Referenced Param) where toJSON :: Referenced Param -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/parameters/"
instance ToJSON (Referenced Response) where toJSON :: Referenced Response -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/responses/"
instance ToJSON (Referenced RequestBody) where toJSON :: Referenced RequestBody -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/requestBodies/"
instance ToJSON (Referenced Example) where toJSON :: Referenced Example -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/examples/"
instance ToJSON (Referenced Header) where toJSON :: Referenced Header -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/headers/"
instance ToJSON (Referenced Link) where toJSON :: Referenced Link -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/links/"
instance ToJSON (Referenced Callback) where toJSON :: Referenced Callback -> Value
toJSON = forall a. ToJSON a => TagName -> Referenced a -> Value
referencedToJSON TagName
"#/components/callbacks/"
instance ToJSON AdditionalProperties where
toJSON :: AdditionalProperties -> Value
toJSON (AdditionalPropertiesAllowed Bool
b) = forall a. ToJSON a => a -> Value
toJSON Bool
b
toJSON (AdditionalPropertiesSchema Referenced Schema
s) = forall a. ToJSON a => a -> Value
toJSON Referenced Schema
s
instance ToJSON ExpressionOrValue where
toJSON :: ExpressionOrValue -> Value
toJSON (Expression TagName
expr) = forall a. ToJSON a => a -> Value
toJSON TagName
expr
toJSON (Value Value
val) = forall a. ToJSON a => a -> Value
toJSON Value
val
instance ToJSON Callback where
toJSON :: Callback -> Value
toJSON (Callback InsOrdHashMap TagName PathItem
ps) = forall a. ToJSON a => a -> Value
toJSON InsOrdHashMap TagName PathItem
ps
instance FromJSON OpenApiSpecVersion where
parseJSON :: Value -> Parser OpenApiSpecVersion
parseJSON = forall a. FilePath -> (TagName -> Parser a) -> Value -> Parser a
withText FilePath
"OpenApiSpecVersion" forall a b. (a -> b) -> a -> b
$ \TagName
str ->
let validatedVersion :: Either String Version
validatedVersion :: Either FilePath Version
validatedVersion = do
Version
parsedVersion <- TagName -> Either FilePath Version
readVersion TagName
str
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Version
parsedVersion forall a. Ord a => a -> a -> Bool
>= Version
lowerOpenApiSpecVersion) Bool -> Bool -> Bool
&& (Version
parsedVersion forall a. Ord a => a -> a -> Bool
<= Version
upperOpenApiSpecVersion)) forall a b. (a -> b) -> a -> b
$
forall a b. a -> Either a b
Left (FilePath
"The provided version " forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
parsedVersion forall a. Semigroup a => a -> a -> a
<> FilePath
" is out of the allowed range >=" forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
lowerOpenApiSpecVersion forall a. Semigroup a => a -> a -> a
<> FilePath
" && <=" forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
upperOpenApiSpecVersion)
forall (m :: * -> *) a. Monad m => a -> m a
return Version
parsedVersion
in
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> OpenApiSpecVersion
OpenApiSpecVersion) Either FilePath Version
validatedVersion
where
readVersion :: Text -> Either String Version
readVersion :: TagName -> Either FilePath Version
readVersion TagName
v = case forall a. ReadP a -> ReadS a
readP_to_S ReadP Version
parseVersion (TagName -> FilePath
Text.unpack TagName
v) of
[] -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath
"Failed to parse as a version string " forall a. Semigroup a => a -> a -> a
<> TagName -> FilePath
Text.unpack TagName
v
[(Version, FilePath)]
solutions -> forall a b. b -> Either a b
Right (forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last forall a b. (a -> b) -> a -> b
$ [(Version, FilePath)]
solutions)
instance FromJSON MediaType where
parseJSON :: Value -> Parser MediaType
parseJSON = forall a. FilePath -> (TagName -> Parser a) -> Value -> Parser a
withText FilePath
"MediaType" forall a b. (a -> b) -> a -> b
$ \TagName
str ->
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$ FilePath
"Invalid media type literal " forall a. Semigroup a => a -> a -> a
<> TagName -> FilePath
Text.unpack TagName
str) forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Accept a => ByteString -> Maybe a
parseAccept forall a b. (a -> b) -> a -> b
$ TagName -> ByteString
encodeUtf8 TagName
str
instance FromJSONKey MediaType where
fromJSONKey :: FromJSONKeyFunction MediaType
fromJSONKey = forall a. (TagName -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser (forall a. FromJSON a => Value -> Parser a
parseJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. TagName -> Value
String)
instance (Eq p, FromJSON p, AesonDefaultValue p) => FromJSON (OAuth2Flow p) where
parseJSON :: Value -> Parser (OAuth2Flow p)
parseJSON = 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 = 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
(TagName
t :: Text) <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
case TagName
t of
TagName
"http" -> do
TagName
scheme <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"scheme"
HttpSchemeType -> SecuritySchemeType
SecuritySchemeHttp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case TagName
scheme of
TagName
"bearer" -> Maybe TagName -> HttpSchemeType
HttpSchemeBearer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:! Key
"bearerFormat")
TagName
"basic" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure HttpSchemeType
HttpSchemeBasic
TagName
t -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ TagName -> HttpSchemeType
HttpSchemeCustom TagName
t
TagName
"apiKey" -> ApiKeyParams -> SecuritySchemeType
SecuritySchemeApiKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
TagName
"oauth2" -> OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"flows")
TagName
"openIdConnect" -> URL -> SecuritySchemeType
SecuritySchemeOpenIdConnect forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"openIdConnectUrl")
TagName
_ -> forall (f :: * -> *) a. Alternative f => f a
empty
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON OpenApi where
parseJSON :: Value -> Parser OpenApi
parseJSON = 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 = 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 = 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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Schema -> Schema
nullaryCleanup forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just ([Referenced Schema] -> OpenApiItems
OpenApiItemsArray [])
then Schema
s { _schemaExample :: Maybe Value
_schemaExample = forall a. Maybe a
Nothing
, _schemaMaxItems :: Maybe Integer
_schemaMaxItems = forall a. Maybe a
Nothing
}
else Schema
s
instance FromJSON Header where
parseJSON :: Value -> Parser Header
parseJSON = 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)
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null Object
obj = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [Referenced Schema] -> OpenApiItems
OpenApiItemsArray []
| Bool
otherwise = Referenced Schema -> OpenApiItems
OpenApiItemsObject forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
parseJSON js :: Value
js@(Array Array
_) = [Referenced Schema] -> OpenApiItems
OpenApiItemsArray forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON Components where
parseJSON :: Value -> Parser Components
parseJSON = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. IsString a => FilePath -> a
fromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON Param where
parseJSON :: Value -> Parser Param
parseJSON = 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
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object (forall v. Key -> KeyMap v -> KeyMap v
deleteKey Key
"default" Object
o))
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON Example where
parseJSON :: Value -> Parser Example
parseJSON = 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 = 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 = 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 = 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON RequestBody where
parseJSON :: Value -> Parser RequestBody
parseJSON = 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 = 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 = 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 = 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) = TagName -> Reference
Reference forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"$ref"
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
referencedParseJSON :: FromJSON a => Text -> Value -> JSON.Parser (Referenced a)
referencedParseJSON :: forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
prefix js :: Value
js@(Object Object
o) = do
Maybe TagName
ms <- Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"$ref"
case Maybe TagName
ms of
Maybe TagName
Nothing -> forall a. a -> Referenced a
Inline forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
Just TagName
s -> forall a. Reference -> Referenced a
Ref forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TagName -> Parser Reference
parseRef TagName
s
where
parseRef :: TagName -> Parser Reference
parseRef TagName
s = do
case TagName -> TagName -> Maybe TagName
Text.stripPrefix TagName
prefix TagName
s of
Maybe TagName
Nothing -> forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$ FilePath
"expected $ref of the form \"" forall a. Semigroup a => a -> a -> a
<> TagName -> FilePath
Text.unpack TagName
prefix forall a. Semigroup a => a -> a -> a
<> FilePath
"*\", but got " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> FilePath
show TagName
s
Just TagName
suffix -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (TagName -> Reference
Reference TagName
suffix)
referencedParseJSON TagName
_ Value
_ = 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 = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/schemas/"
instance FromJSON (Referenced Param) where parseJSON :: Value -> Parser (Referenced Param)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/parameters/"
instance FromJSON (Referenced Response) where parseJSON :: Value -> Parser (Referenced Response)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/responses/"
instance FromJSON (Referenced RequestBody) where parseJSON :: Value -> Parser (Referenced RequestBody)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/requestBodies/"
instance FromJSON (Referenced Example) where parseJSON :: Value -> Parser (Referenced Example)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/examples/"
instance FromJSON (Referenced Header) where parseJSON :: Value -> Parser (Referenced Header)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/headers/"
instance FromJSON (Referenced Link) where parseJSON :: Value -> Parser (Referenced Link)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/links/"
instance FromJSON (Referenced Callback) where parseJSON :: Value -> Parser (Referenced Callback)
parseJSON = forall a. FromJSON a => TagName -> Value -> Parser (Referenced a)
referencedParseJSON TagName
"#/components/callbacks/"
instance FromJSON Xml where
parseJSON :: Value -> Parser Xml
parseJSON = 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) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> AdditionalProperties
AdditionalPropertiesAllowed Bool
b
parseJSON Value
js = Referenced Schema -> AdditionalProperties
AdditionalPropertiesSchema forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON ExpressionOrValue where
parseJSON :: Value -> Parser ExpressionOrValue
parseJSON (String TagName
expr) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ TagName -> ExpressionOrValue
Expression TagName
expr
parseJSON Value
v = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Value -> ExpressionOrValue
Value Value
v
instance FromJSON Callback where
parseJSON :: Value -> Parser Callback
parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InsOrdHashMap TagName PathItem -> Callback
Callback forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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" forall a b. a -> (a -> b) -> b
& Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject 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" forall a b. a -> (a -> b) -> b
& Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject 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" forall a b. a -> (a -> b) -> b
& Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject 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" forall a b. a -> (a -> b) -> b
& Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"paramSchema"
instance HasSwaggerAesonOptions OpenApiSpecVersion where
swaggerAesonOptions :: Proxy OpenApiSpecVersion -> SwaggerAesonOptions
swaggerAesonOptions Proxy OpenApiSpecVersion
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"openapi"
instance HasSwaggerAesonOptions OpenApi where
swaggerAesonOptions :: Proxy OpenApi -> SwaggerAesonOptions
swaggerAesonOptions Proxy OpenApi
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"swagger"
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 Version where
defaultValue :: Maybe Version
defaultValue = forall a. a -> Maybe a
Just ([Int] -> Version
makeVersion [Int
3,Int
0,Int
0])
instance AesonDefaultValue OpenApiSpecVersion
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 = forall a. a -> Maybe a
Just forall a. Monoid a => a
mempty
instance AesonDefaultValue Info
instance AesonDefaultValue ParamLocation
instance AesonDefaultValue Link
instance AesonDefaultValue SecurityDefinitions where
defaultValue :: Maybe SecurityDefinitions
defaultValue = forall a. a -> Maybe a
Just forall a. Monoid a => a
mempty