{-# 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
(OpenApi -> OpenApi -> Bool)
-> (OpenApi -> OpenApi -> Bool) -> Eq OpenApi
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenApi -> OpenApi -> Bool
== :: OpenApi -> OpenApi -> Bool
$c/= :: OpenApi -> OpenApi -> Bool
/= :: OpenApi -> OpenApi -> Bool
Eq, Int -> OpenApi -> ShowS
[OpenApi] -> ShowS
OpenApi -> FilePath
(Int -> OpenApi -> ShowS)
-> (OpenApi -> FilePath) -> ([OpenApi] -> ShowS) -> Show OpenApi
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenApi -> ShowS
showsPrec :: Int -> OpenApi -> ShowS
$cshow :: OpenApi -> FilePath
show :: OpenApi -> FilePath
$cshowList :: [OpenApi] -> ShowS
showList :: [OpenApi] -> ShowS
Show, (forall x. OpenApi -> Rep OpenApi x)
-> (forall x. Rep OpenApi x -> OpenApi) -> Generic OpenApi
forall x. Rep OpenApi x -> OpenApi
forall x. OpenApi -> Rep OpenApi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OpenApi -> Rep OpenApi x
from :: forall x. OpenApi -> Rep OpenApi x
$cto :: forall x. Rep OpenApi x -> OpenApi
to :: forall x. Rep OpenApi x -> OpenApi
Generic, Typeable OpenApi
Typeable OpenApi =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApi -> c OpenApi)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApi)
-> (OpenApi -> Constr)
-> (OpenApi -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApi))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenApi))
-> ((forall b. Data b => b -> b) -> OpenApi -> OpenApi)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApi -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApi -> r)
-> (forall u. (forall d. Data d => d -> u) -> OpenApi -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> OpenApi -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApi -> m OpenApi)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApi -> m OpenApi)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApi -> m OpenApi)
-> Data OpenApi
OpenApi -> Constr
OpenApi -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApi -> c OpenApi
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApi -> c OpenApi
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApi
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApi
$ctoConstr :: OpenApi -> Constr
toConstr :: OpenApi -> Constr
$cdataTypeOf :: OpenApi -> DataType
dataTypeOf :: OpenApi -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApi)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApi)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenApi)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenApi)
$cgmapT :: (forall b. Data b => b -> b) -> OpenApi -> OpenApi
gmapT :: (forall b. Data b => b -> b) -> OpenApi -> OpenApi
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApi -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApi -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApi -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApi -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApi -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApi -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApi -> m OpenApi
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApi -> m 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 -> Text
_infoTitle :: Text
, Info -> Maybe Text
_infoDescription :: Maybe Text
, Info -> Maybe Text
_infoTermsOfService :: Maybe Text
, Info -> Maybe Contact
_infoContact :: Maybe Contact
, Info -> Maybe License
_infoLicense :: Maybe License
, Info -> Text
_infoVersion :: Text
} deriving (Info -> Info -> Bool
(Info -> Info -> Bool) -> (Info -> Info -> Bool) -> Eq Info
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Info -> Info -> Bool
== :: Info -> Info -> Bool
$c/= :: Info -> Info -> Bool
/= :: Info -> Info -> Bool
Eq, Int -> Info -> ShowS
[Info] -> ShowS
Info -> FilePath
(Int -> Info -> ShowS)
-> (Info -> FilePath) -> ([Info] -> ShowS) -> Show Info
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Info -> ShowS
showsPrec :: Int -> Info -> ShowS
$cshow :: Info -> FilePath
show :: Info -> FilePath
$cshowList :: [Info] -> ShowS
showList :: [Info] -> ShowS
Show, (forall x. Info -> Rep Info x)
-> (forall x. Rep Info x -> Info) -> Generic Info
forall x. Rep Info x -> Info
forall x. Info -> Rep Info x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Info -> Rep Info x
from :: forall x. Info -> Rep Info x
$cto :: forall x. Rep Info x -> Info
to :: forall x. Rep Info x -> Info
Generic, Typeable Info
Typeable Info =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info)
-> (Info -> Constr)
-> (Info -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Info))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info))
-> ((forall b. Data b => b -> b) -> Info -> Info)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r)
-> (forall u. (forall d. Data d => d -> u) -> Info -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Info -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Info -> m Info)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info)
-> Data Info
Info -> Constr
Info -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Info -> c Info
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Info
$ctoConstr :: Info -> Constr
toConstr :: Info -> Constr
$cdataTypeOf :: Info -> DataType
dataTypeOf :: Info -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Info)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Info)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info)
$cgmapT :: (forall b. Data b => b -> b) -> Info -> Info
gmapT :: (forall b. Data b => b -> b) -> Info -> Info
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Info -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Info -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Info -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Info -> m Info
Data, Typeable)
data Contact = Contact
{
Contact -> Maybe Text
_contactName :: Maybe Text
, Contact -> Maybe URL
_contactUrl :: Maybe URL
, Contact -> Maybe Text
_contactEmail :: Maybe Text
} deriving (Contact -> Contact -> Bool
(Contact -> Contact -> Bool)
-> (Contact -> Contact -> Bool) -> Eq Contact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Contact -> Contact -> Bool
== :: Contact -> Contact -> Bool
$c/= :: Contact -> Contact -> Bool
/= :: Contact -> Contact -> Bool
Eq, Int -> Contact -> ShowS
[Contact] -> ShowS
Contact -> FilePath
(Int -> Contact -> ShowS)
-> (Contact -> FilePath) -> ([Contact] -> ShowS) -> Show Contact
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Contact -> ShowS
showsPrec :: Int -> Contact -> ShowS
$cshow :: Contact -> FilePath
show :: Contact -> FilePath
$cshowList :: [Contact] -> ShowS
showList :: [Contact] -> ShowS
Show, (forall x. Contact -> Rep Contact x)
-> (forall x. Rep Contact x -> Contact) -> Generic Contact
forall x. Rep Contact x -> Contact
forall x. Contact -> Rep Contact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Contact -> Rep Contact x
from :: forall x. Contact -> Rep Contact x
$cto :: forall x. Rep Contact x -> Contact
to :: forall x. Rep Contact x -> Contact
Generic, Typeable Contact
Typeable Contact =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact)
-> (Contact -> Constr)
-> (Contact -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contact))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact))
-> ((forall b. Data b => b -> b) -> Contact -> Contact)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r)
-> (forall u. (forall d. Data d => d -> u) -> Contact -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact)
-> Data Contact
Contact -> Constr
Contact -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contact -> c Contact
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contact
$ctoConstr :: Contact -> Constr
toConstr :: Contact -> Constr
$cdataTypeOf :: Contact -> DataType
dataTypeOf :: Contact -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contact)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contact)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact)
$cgmapT :: (forall b. Data b => b -> b) -> Contact -> Contact
gmapT :: (forall b. Data b => b -> b) -> Contact -> Contact
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contact -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Contact -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Contact -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contact -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contact -> m Contact
Data, Typeable)
data License = License
{
License -> Text
_licenseName :: Text
, License -> Maybe URL
_licenseUrl :: Maybe URL
} deriving (License -> License -> Bool
(License -> License -> Bool)
-> (License -> License -> Bool) -> Eq License
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: License -> License -> Bool
== :: License -> License -> Bool
$c/= :: License -> License -> Bool
/= :: License -> License -> Bool
Eq, Int -> License -> ShowS
[License] -> ShowS
License -> FilePath
(Int -> License -> ShowS)
-> (License -> FilePath) -> ([License] -> ShowS) -> Show License
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> License -> ShowS
showsPrec :: Int -> License -> ShowS
$cshow :: License -> FilePath
show :: License -> FilePath
$cshowList :: [License] -> ShowS
showList :: [License] -> ShowS
Show, (forall x. License -> Rep License x)
-> (forall x. Rep License x -> License) -> Generic License
forall x. Rep License x -> License
forall x. License -> Rep License x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. License -> Rep License x
from :: forall x. License -> Rep License x
$cto :: forall x. Rep License x -> License
to :: forall x. Rep License x -> License
Generic, Typeable License
Typeable License =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License)
-> (License -> Constr)
-> (License -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License))
-> ((forall b. Data b => b -> b) -> License -> License)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall u. (forall d. Data d => d -> u) -> License -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> License -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> Data License
License -> Constr
License -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
$ctoConstr :: License -> Constr
toConstr :: License -> Constr
$cdataTypeOf :: License -> DataType
dataTypeOf :: License -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cgmapT :: (forall b. Data b => b -> b) -> License -> License
gmapT :: (forall b. Data b => b -> b) -> License -> License
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
Data, Typeable)
instance IsString License where
fromString :: FilePath -> License
fromString FilePath
s = Text -> Maybe URL -> License
License (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe URL
forall a. Maybe a
Nothing
data Server = Server
{
Server -> Text
_serverUrl :: Text
, Server -> Maybe Text
_serverDescription :: Maybe Text
, Server -> InsOrdHashMap Text ServerVariable
_serverVariables :: InsOrdHashMap Text ServerVariable
} deriving (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
/= :: Server -> Server -> Bool
Eq, Int -> Server -> ShowS
[Server] -> ShowS
Server -> FilePath
(Int -> Server -> ShowS)
-> (Server -> FilePath) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Server -> ShowS
showsPrec :: Int -> Server -> ShowS
$cshow :: Server -> FilePath
show :: Server -> FilePath
$cshowList :: [Server] -> ShowS
showList :: [Server] -> ShowS
Show, (forall x. Server -> Rep Server x)
-> (forall x. Rep Server x -> Server) -> Generic Server
forall x. Rep Server x -> Server
forall x. Server -> Rep Server x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Server -> Rep Server x
from :: forall x. Server -> Rep Server x
$cto :: forall x. Rep Server x -> Server
to :: forall x. Rep Server x -> Server
Generic, Typeable Server
Typeable Server =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server)
-> (Server -> Constr)
-> (Server -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Server))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server))
-> ((forall b. Data b => b -> b) -> Server -> Server)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Server -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Server -> r)
-> (forall u. (forall d. Data d => d -> u) -> Server -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Server -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Server -> m Server)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server)
-> Data Server
Server -> Constr
Server -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Server -> c Server
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Server
$ctoConstr :: Server -> Constr
toConstr :: Server -> Constr
$cdataTypeOf :: Server -> DataType
dataTypeOf :: Server -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Server)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Server)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server)
$cgmapT :: (forall b. Data b => b -> b) -> Server -> Server
gmapT :: (forall b. Data b => b -> b) -> Server -> Server
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Server -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Server -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Server -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Server -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Server -> m Server
Data, Typeable)
data ServerVariable = ServerVariable
{
ServerVariable -> Maybe (InsOrdHashSet Text)
_serverVariableEnum :: Maybe (InsOrdHashSet Text)
, ServerVariable -> Text
_serverVariableDefault :: Text
, ServerVariable -> Maybe Text
_serverVariableDescription :: Maybe Text
} deriving (ServerVariable -> ServerVariable -> Bool
(ServerVariable -> ServerVariable -> Bool)
-> (ServerVariable -> ServerVariable -> Bool) -> Eq ServerVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerVariable -> ServerVariable -> Bool
== :: ServerVariable -> ServerVariable -> Bool
$c/= :: ServerVariable -> ServerVariable -> Bool
/= :: ServerVariable -> ServerVariable -> Bool
Eq, Int -> ServerVariable -> ShowS
[ServerVariable] -> ShowS
ServerVariable -> FilePath
(Int -> ServerVariable -> ShowS)
-> (ServerVariable -> FilePath)
-> ([ServerVariable] -> ShowS)
-> Show ServerVariable
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerVariable -> ShowS
showsPrec :: Int -> ServerVariable -> ShowS
$cshow :: ServerVariable -> FilePath
show :: ServerVariable -> FilePath
$cshowList :: [ServerVariable] -> ShowS
showList :: [ServerVariable] -> ShowS
Show, (forall x. ServerVariable -> Rep ServerVariable x)
-> (forall x. Rep ServerVariable x -> ServerVariable)
-> Generic ServerVariable
forall x. Rep ServerVariable x -> ServerVariable
forall x. ServerVariable -> Rep ServerVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServerVariable -> Rep ServerVariable x
from :: forall x. ServerVariable -> Rep ServerVariable x
$cto :: forall x. Rep ServerVariable x -> ServerVariable
to :: forall x. Rep ServerVariable x -> ServerVariable
Generic, Typeable ServerVariable
Typeable ServerVariable =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable)
-> (ServerVariable -> Constr)
-> (ServerVariable -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ServerVariable))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable))
-> ((forall b. Data b => b -> b)
-> ServerVariable -> ServerVariable)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ServerVariable -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable)
-> Data ServerVariable
ServerVariable -> Constr
ServerVariable -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ServerVariable -> c ServerVariable
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ServerVariable
$ctoConstr :: ServerVariable -> Constr
toConstr :: ServerVariable -> Constr
$cdataTypeOf :: ServerVariable -> DataType
dataTypeOf :: ServerVariable -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ServerVariable)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ServerVariable)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ServerVariable)
$cgmapT :: (forall b. Data b => b -> b) -> ServerVariable -> ServerVariable
gmapT :: (forall b. Data b => b -> b) -> ServerVariable -> ServerVariable
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ServerVariable -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ServerVariable -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ServerVariable -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ServerVariable -> m ServerVariable
Data, Typeable)
instance IsString Server where
fromString :: FilePath -> Server
fromString FilePath
s = Text -> Maybe Text -> InsOrdHashMap Text ServerVariable -> Server
Server (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe Text
forall a. Maybe a
Nothing InsOrdHashMap Text ServerVariable
forall a. Monoid a => a
mempty
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
(Components -> Components -> Bool)
-> (Components -> Components -> Bool) -> Eq Components
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Components -> Components -> Bool
== :: Components -> Components -> Bool
$c/= :: Components -> Components -> Bool
/= :: Components -> Components -> Bool
Eq, Int -> Components -> ShowS
[Components] -> ShowS
Components -> FilePath
(Int -> Components -> ShowS)
-> (Components -> FilePath)
-> ([Components] -> ShowS)
-> Show Components
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Components -> ShowS
showsPrec :: Int -> Components -> ShowS
$cshow :: Components -> FilePath
show :: Components -> FilePath
$cshowList :: [Components] -> ShowS
showList :: [Components] -> ShowS
Show, (forall x. Components -> Rep Components x)
-> (forall x. Rep Components x -> Components) -> Generic Components
forall x. Rep Components x -> Components
forall x. Components -> Rep Components x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Components -> Rep Components x
from :: forall x. Components -> Rep Components x
$cto :: forall x. Rep Components x -> Components
to :: forall x. Rep Components x -> Components
Generic, Typeable Components
Typeable Components =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components)
-> (Components -> Constr)
-> (Components -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Components))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Components))
-> ((forall b. Data b => b -> b) -> Components -> Components)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r)
-> (forall u. (forall d. Data d => d -> u) -> Components -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Components -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Components -> m Components)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components)
-> Data Components
Components -> Constr
Components -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Components -> c Components
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Components
$ctoConstr :: Components -> Constr
toConstr :: Components -> Constr
$cdataTypeOf :: Components -> DataType
dataTypeOf :: Components -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Components)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Components)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Components)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Components)
$cgmapT :: (forall b. Data b => b -> b) -> Components -> Components
gmapT :: (forall b. Data b => b -> b) -> Components -> Components
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Components -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Components -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Components -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Components -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Components -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Components -> m Components
Data, Typeable)
data PathItem = PathItem
{
PathItem -> Maybe Text
_pathItemSummary :: Maybe Text
, PathItem -> Maybe Text
_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
(PathItem -> PathItem -> Bool)
-> (PathItem -> PathItem -> Bool) -> Eq PathItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathItem -> PathItem -> Bool
== :: PathItem -> PathItem -> Bool
$c/= :: PathItem -> PathItem -> Bool
/= :: PathItem -> PathItem -> Bool
Eq, Int -> PathItem -> ShowS
[PathItem] -> ShowS
PathItem -> FilePath
(Int -> PathItem -> ShowS)
-> (PathItem -> FilePath) -> ([PathItem] -> ShowS) -> Show PathItem
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathItem -> ShowS
showsPrec :: Int -> PathItem -> ShowS
$cshow :: PathItem -> FilePath
show :: PathItem -> FilePath
$cshowList :: [PathItem] -> ShowS
showList :: [PathItem] -> ShowS
Show, (forall x. PathItem -> Rep PathItem x)
-> (forall x. Rep PathItem x -> PathItem) -> Generic PathItem
forall x. Rep PathItem x -> PathItem
forall x. PathItem -> Rep PathItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathItem -> Rep PathItem x
from :: forall x. PathItem -> Rep PathItem x
$cto :: forall x. Rep PathItem x -> PathItem
to :: forall x. Rep PathItem x -> PathItem
Generic, Typeable PathItem
Typeable PathItem =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem)
-> (PathItem -> Constr)
-> (PathItem -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathItem))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem))
-> ((forall b. Data b => b -> b) -> PathItem -> PathItem)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r)
-> (forall u. (forall d. Data d => d -> u) -> PathItem -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem)
-> Data PathItem
PathItem -> Constr
PathItem -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathItem -> c PathItem
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathItem
$ctoConstr :: PathItem -> Constr
toConstr :: PathItem -> Constr
$cdataTypeOf :: PathItem -> DataType
dataTypeOf :: PathItem -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathItem)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathItem)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathItem)
$cgmapT :: (forall b. Data b => b -> b) -> PathItem -> PathItem
gmapT :: (forall b. Data b => b -> b) -> PathItem -> PathItem
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathItem -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PathItem -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathItem -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathItem -> m PathItem
Data, Typeable)
data Operation = Operation
{
Operation -> InsOrdHashSet Text
_operationTags :: InsOrdHashSet TagName
, Operation -> Maybe Text
_operationSummary :: Maybe Text
, Operation -> Maybe Text
_operationDescription :: Maybe Text
, Operation -> Maybe ExternalDocs
_operationExternalDocs :: Maybe ExternalDocs
, Operation -> Maybe Text
_operationOperationId :: Maybe Text
, Operation -> [Referenced Param]
_operationParameters :: [Referenced Param]
, Operation -> Maybe (Referenced RequestBody)
_operationRequestBody :: Maybe (Referenced RequestBody)
, Operation -> Responses
_operationResponses :: Responses
, Operation -> InsOrdHashMap Text (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
(Operation -> Operation -> Bool)
-> (Operation -> Operation -> Bool) -> Eq Operation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Operation -> Operation -> Bool
== :: Operation -> Operation -> Bool
$c/= :: Operation -> Operation -> Bool
/= :: Operation -> Operation -> Bool
Eq, Int -> Operation -> ShowS
[Operation] -> ShowS
Operation -> FilePath
(Int -> Operation -> ShowS)
-> (Operation -> FilePath)
-> ([Operation] -> ShowS)
-> Show Operation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Operation -> ShowS
showsPrec :: Int -> Operation -> ShowS
$cshow :: Operation -> FilePath
show :: Operation -> FilePath
$cshowList :: [Operation] -> ShowS
showList :: [Operation] -> ShowS
Show, (forall x. Operation -> Rep Operation x)
-> (forall x. Rep Operation x -> Operation) -> Generic Operation
forall x. Rep Operation x -> Operation
forall x. Operation -> Rep Operation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Operation -> Rep Operation x
from :: forall x. Operation -> Rep Operation x
$cto :: forall x. Rep Operation x -> Operation
to :: forall x. Rep Operation x -> Operation
Generic, Typeable Operation
Typeable Operation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation)
-> (Operation -> Constr)
-> (Operation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation))
-> ((forall b. Data b => b -> b) -> Operation -> Operation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r)
-> (forall u. (forall d. Data d => d -> u) -> Operation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Operation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation)
-> Data Operation
Operation -> Constr
Operation -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operation -> c Operation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operation
$ctoConstr :: Operation -> Constr
toConstr :: Operation -> Constr
$cdataTypeOf :: Operation -> DataType
dataTypeOf :: Operation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operation)
$cgmapT :: (forall b. Data b => b -> b) -> Operation -> Operation
gmapT :: (forall b. Data b => b -> b) -> Operation -> Operation
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Operation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Operation -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operation -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m Operation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operation -> m 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 -> c (Map ByteString ByteString -> MediaType) -> c MediaType
forall b r. Data b => c (b -> r) -> c r
k (c (ByteString -> Map ByteString ByteString -> MediaType)
-> c (Map ByteString ByteString -> MediaType)
forall b r. Data b => c (b -> r) -> c r
k (c (ByteString
-> ByteString -> Map ByteString ByteString -> MediaType)
-> c (ByteString -> Map ByteString ByteString -> MediaType)
forall b r. Data b => c (b -> r) -> c r
k ((ByteString
-> ByteString -> Map ByteString ByteString -> MediaType)
-> c (ByteString
-> ByteString -> Map ByteString ByteString -> MediaType)
forall r. r -> c r
z (\ByteString
main ByteString
sub Map ByteString ByteString
params -> (MediaType -> (ByteString, ByteString) -> MediaType)
-> MediaType -> [(ByteString, ByteString)] -> MediaType
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl MediaType -> (ByteString, ByteString) -> MediaType
(/:) (ByteString
main ByteString -> ByteString -> MediaType
// ByteString
sub) (Map ByteString ByteString -> [(ByteString, ByteString)]
forall k a. Map k a -> [(k, a)]
Map.toList Map ByteString ByteString
params)))))
Int
_ -> FilePath -> c MediaType
forall a. HasCallStack => FilePath -> a
error (FilePath -> c MediaType) -> FilePath -> c MediaType
forall a b. (a -> b) -> a -> b
$ FilePath
"Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" is not of type MediaType."
toConstr :: MediaType -> Constr
toConstr MediaType
_ = Constr
mediaTypeConstr
dataTypeOf :: MediaType -> DataType
dataTypeOf MediaType
_ = DataType
mediaTypeData
mediaTypeConstr :: Constr
mediaTypeConstr = DataType -> FilePath -> [FilePath] -> Fixity -> Constr
mkConstr DataType
mediaTypeData FilePath
"MediaType" [] Fixity
Prefix
mediaTypeData :: DataType
mediaTypeData = FilePath -> [Constr] -> DataType
mkDataType FilePath
"MediaType" [Constr
mediaTypeConstr]
instance Hashable MediaType where
hashWithSalt :: Int -> MediaType -> Int
hashWithSalt Int
salt MediaType
mt = Int
salt Int -> FilePath -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` MediaType -> FilePath
forall a. Show a => a -> FilePath
show MediaType
mt
data RequestBody = RequestBody
{
RequestBody -> Maybe Text
_requestBodyDescription :: Maybe Text
, RequestBody -> InsOrdHashMap MediaType MediaTypeObject
_requestBodyContent :: InsOrdHashMap MediaType MediaTypeObject
, RequestBody -> Maybe Bool
_requestBodyRequired :: Maybe Bool
} deriving (RequestBody -> RequestBody -> Bool
(RequestBody -> RequestBody -> Bool)
-> (RequestBody -> RequestBody -> Bool) -> Eq RequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestBody -> RequestBody -> Bool
== :: RequestBody -> RequestBody -> Bool
$c/= :: RequestBody -> RequestBody -> Bool
/= :: RequestBody -> RequestBody -> Bool
Eq, Int -> RequestBody -> ShowS
[RequestBody] -> ShowS
RequestBody -> FilePath
(Int -> RequestBody -> ShowS)
-> (RequestBody -> FilePath)
-> ([RequestBody] -> ShowS)
-> Show RequestBody
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestBody -> ShowS
showsPrec :: Int -> RequestBody -> ShowS
$cshow :: RequestBody -> FilePath
show :: RequestBody -> FilePath
$cshowList :: [RequestBody] -> ShowS
showList :: [RequestBody] -> ShowS
Show, (forall x. RequestBody -> Rep RequestBody x)
-> (forall x. Rep RequestBody x -> RequestBody)
-> Generic RequestBody
forall x. Rep RequestBody x -> RequestBody
forall x. RequestBody -> Rep RequestBody x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestBody -> Rep RequestBody x
from :: forall x. RequestBody -> Rep RequestBody x
$cto :: forall x. Rep RequestBody x -> RequestBody
to :: forall x. Rep RequestBody x -> RequestBody
Generic, Typeable RequestBody
Typeable RequestBody =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RequestBody -> c RequestBody)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RequestBody)
-> (RequestBody -> Constr)
-> (RequestBody -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RequestBody))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RequestBody))
-> ((forall b. Data b => b -> b) -> RequestBody -> RequestBody)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RequestBody -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RequestBody -> r)
-> (forall u. (forall d. Data d => d -> u) -> RequestBody -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RequestBody -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RequestBody -> m RequestBody)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RequestBody -> m RequestBody)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RequestBody -> m RequestBody)
-> Data RequestBody
RequestBody -> Constr
RequestBody -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RequestBody -> c RequestBody
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RequestBody -> c RequestBody
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RequestBody
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RequestBody
$ctoConstr :: RequestBody -> Constr
toConstr :: RequestBody -> Constr
$cdataTypeOf :: RequestBody -> DataType
dataTypeOf :: RequestBody -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RequestBody)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RequestBody)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RequestBody)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RequestBody)
$cgmapT :: (forall b. Data b => b -> b) -> RequestBody -> RequestBody
gmapT :: (forall b. Data b => b -> b) -> RequestBody -> RequestBody
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RequestBody -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RequestBody -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RequestBody -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RequestBody -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RequestBody -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RequestBody -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RequestBody -> m RequestBody
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RequestBody -> m RequestBody
Data, Typeable)
data MediaTypeObject = MediaTypeObject
{ MediaTypeObject -> Maybe (Referenced Schema)
_mediaTypeObjectSchema :: Maybe (Referenced Schema)
, MediaTypeObject -> Maybe Value
_mediaTypeObjectExample :: Maybe Value
, MediaTypeObject -> InsOrdHashMap Text (Referenced Example)
_mediaTypeObjectExamples :: InsOrdHashMap Text (Referenced Example)
, MediaTypeObject -> InsOrdHashMap Text Encoding
_mediaTypeObjectEncoding :: InsOrdHashMap Text Encoding
} deriving (MediaTypeObject -> MediaTypeObject -> Bool
(MediaTypeObject -> MediaTypeObject -> Bool)
-> (MediaTypeObject -> MediaTypeObject -> Bool)
-> Eq MediaTypeObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MediaTypeObject -> MediaTypeObject -> Bool
== :: MediaTypeObject -> MediaTypeObject -> Bool
$c/= :: MediaTypeObject -> MediaTypeObject -> Bool
/= :: MediaTypeObject -> MediaTypeObject -> Bool
Eq, Int -> MediaTypeObject -> ShowS
[MediaTypeObject] -> ShowS
MediaTypeObject -> FilePath
(Int -> MediaTypeObject -> ShowS)
-> (MediaTypeObject -> FilePath)
-> ([MediaTypeObject] -> ShowS)
-> Show MediaTypeObject
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MediaTypeObject -> ShowS
showsPrec :: Int -> MediaTypeObject -> ShowS
$cshow :: MediaTypeObject -> FilePath
show :: MediaTypeObject -> FilePath
$cshowList :: [MediaTypeObject] -> ShowS
showList :: [MediaTypeObject] -> ShowS
Show, (forall x. MediaTypeObject -> Rep MediaTypeObject x)
-> (forall x. Rep MediaTypeObject x -> MediaTypeObject)
-> Generic MediaTypeObject
forall x. Rep MediaTypeObject x -> MediaTypeObject
forall x. MediaTypeObject -> Rep MediaTypeObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MediaTypeObject -> Rep MediaTypeObject x
from :: forall x. MediaTypeObject -> Rep MediaTypeObject x
$cto :: forall x. Rep MediaTypeObject x -> MediaTypeObject
to :: forall x. Rep MediaTypeObject x -> MediaTypeObject
Generic, Typeable MediaTypeObject
Typeable MediaTypeObject =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject)
-> (MediaTypeObject -> Constr)
-> (MediaTypeObject -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject))
-> ((forall b. Data b => b -> b)
-> MediaTypeObject -> MediaTypeObject)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r)
-> (forall u.
(forall d. Data d => d -> u) -> MediaTypeObject -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject)
-> Data MediaTypeObject
MediaTypeObject -> Constr
MediaTypeObject -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaTypeObject -> c MediaTypeObject
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MediaTypeObject
$ctoConstr :: MediaTypeObject -> Constr
toConstr :: MediaTypeObject -> Constr
$cdataTypeOf :: MediaTypeObject -> DataType
dataTypeOf :: MediaTypeObject -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MediaTypeObject)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MediaTypeObject)
$cgmapT :: (forall b. Data b => b -> b) -> MediaTypeObject -> MediaTypeObject
gmapT :: (forall b. Data b => b -> b) -> MediaTypeObject -> MediaTypeObject
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaTypeObject -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MediaTypeObject -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MediaTypeObject -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MediaTypeObject -> m MediaTypeObject
Data, Typeable)
data Style
= StyleMatrix
| StyleLabel
| StyleForm
| StyleSimple
| StyleSpaceDelimited
| StylePipeDelimited
| StyleDeepObject
deriving (Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
/= :: Style -> Style -> Bool
Eq, Int -> Style -> ShowS
[Style] -> ShowS
Style -> FilePath
(Int -> Style -> ShowS)
-> (Style -> FilePath) -> ([Style] -> ShowS) -> Show Style
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Style -> ShowS
showsPrec :: Int -> Style -> ShowS
$cshow :: Style -> FilePath
show :: Style -> FilePath
$cshowList :: [Style] -> ShowS
showList :: [Style] -> ShowS
Show, (forall x. Style -> Rep Style x)
-> (forall x. Rep Style x -> Style) -> Generic Style
forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Style -> Rep Style x
from :: forall x. Style -> Rep Style x
$cto :: forall x. Rep Style x -> Style
to :: forall x. Rep Style x -> Style
Generic, Typeable Style
Typeable Style =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style)
-> (Style -> Constr)
-> (Style -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style))
-> ((forall b. Data b => b -> b) -> Style -> Style)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall u. (forall d. Data d => d -> u) -> Style -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Style -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style)
-> Data Style
Style -> Constr
Style -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
$ctoConstr :: Style -> Constr
toConstr :: Style -> Constr
$cdataTypeOf :: Style -> DataType
dataTypeOf :: Style -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cgmapT :: (forall b. Data b => b -> b) -> Style -> Style
gmapT :: (forall b. Data b => b -> b) -> Style -> Style
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m 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
(Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool) -> Eq Encoding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Encoding -> Encoding -> Bool
== :: Encoding -> Encoding -> Bool
$c/= :: Encoding -> Encoding -> Bool
/= :: Encoding -> Encoding -> Bool
Eq, Int -> Encoding -> ShowS
[Encoding] -> ShowS
Encoding -> FilePath
(Int -> Encoding -> ShowS)
-> (Encoding -> FilePath) -> ([Encoding] -> ShowS) -> Show Encoding
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Encoding -> ShowS
showsPrec :: Int -> Encoding -> ShowS
$cshow :: Encoding -> FilePath
show :: Encoding -> FilePath
$cshowList :: [Encoding] -> ShowS
showList :: [Encoding] -> ShowS
Show, (forall x. Encoding -> Rep Encoding x)
-> (forall x. Rep Encoding x -> Encoding) -> Generic Encoding
forall x. Rep Encoding x -> Encoding
forall x. Encoding -> Rep Encoding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Encoding -> Rep Encoding x
from :: forall x. Encoding -> Rep Encoding x
$cto :: forall x. Rep Encoding x -> Encoding
to :: forall x. Rep Encoding x -> Encoding
Generic, Typeable Encoding
Typeable Encoding =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding)
-> (Encoding -> Constr)
-> (Encoding -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Encoding))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding))
-> ((forall b. Data b => b -> b) -> Encoding -> Encoding)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r)
-> (forall u. (forall d. Data d => d -> u) -> Encoding -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding)
-> Data Encoding
Encoding -> Constr
Encoding -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Encoding -> c Encoding
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Encoding
$ctoConstr :: Encoding -> Constr
toConstr :: Encoding -> Constr
$cdataTypeOf :: Encoding -> DataType
dataTypeOf :: Encoding -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Encoding)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Encoding)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding)
$cgmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding
gmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Encoding -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Encoding -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Encoding -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Encoding -> m Encoding
Data, Typeable)
newtype MimeList = MimeList { MimeList -> [MediaType]
getMimeList :: [MediaType] }
deriving (MimeList -> MimeList -> Bool
(MimeList -> MimeList -> Bool)
-> (MimeList -> MimeList -> Bool) -> Eq MimeList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MimeList -> MimeList -> Bool
== :: MimeList -> MimeList -> Bool
$c/= :: MimeList -> MimeList -> Bool
/= :: MimeList -> MimeList -> Bool
Eq, Int -> MimeList -> ShowS
[MimeList] -> ShowS
MimeList -> FilePath
(Int -> MimeList -> ShowS)
-> (MimeList -> FilePath) -> ([MimeList] -> ShowS) -> Show MimeList
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MimeList -> ShowS
showsPrec :: Int -> MimeList -> ShowS
$cshow :: MimeList -> FilePath
show :: MimeList -> FilePath
$cshowList :: [MimeList] -> ShowS
showList :: [MimeList] -> ShowS
Show, NonEmpty MimeList -> MimeList
MimeList -> MimeList -> MimeList
(MimeList -> MimeList -> MimeList)
-> (NonEmpty MimeList -> MimeList)
-> (forall b. Integral b => b -> MimeList -> MimeList)
-> Semigroup MimeList
forall b. Integral b => b -> MimeList -> MimeList
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: MimeList -> MimeList -> MimeList
<> :: MimeList -> MimeList -> MimeList
$csconcat :: NonEmpty MimeList -> MimeList
sconcat :: NonEmpty MimeList -> MimeList
$cstimes :: forall b. Integral b => b -> MimeList -> MimeList
stimes :: forall b. Integral b => b -> MimeList -> MimeList
Semigroup, Semigroup MimeList
MimeList
Semigroup MimeList =>
MimeList
-> (MimeList -> MimeList -> MimeList)
-> ([MimeList] -> MimeList)
-> Monoid MimeList
[MimeList] -> MimeList
MimeList -> MimeList -> MimeList
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: MimeList
mempty :: MimeList
$cmappend :: MimeList -> MimeList -> MimeList
mappend :: MimeList -> MimeList -> MimeList
$cmconcat :: [MimeList] -> MimeList
mconcat :: [MimeList] -> 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 -> c ([FilePath] -> MimeList) -> c MimeList
forall b r. Data b => c (b -> r) -> c r
k (([FilePath] -> MimeList) -> c ([FilePath] -> MimeList)
forall r. r -> c r
z ([MediaType] -> MimeList
MimeList ([MediaType] -> MimeList)
-> ([FilePath] -> [MediaType]) -> [FilePath] -> MimeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> MediaType) -> [FilePath] -> [MediaType]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString))
Int
_ -> FilePath -> c MimeList
forall a. HasCallStack => FilePath -> a
error (FilePath -> c MimeList) -> FilePath -> c MimeList
forall a b. (a -> b) -> a -> b
$ FilePath
"Data.Data.gunfold: Constructor " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Constr -> FilePath
forall a. Show a => a -> FilePath
show Constr
c FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" is not of type MimeList."
toConstr :: MimeList -> Constr
toConstr (MimeList [MediaType]
_) = Constr
mimeListConstr
dataTypeOf :: MimeList -> DataType
dataTypeOf MimeList
_ = DataType
mimeListDataType
data Param = Param
{
Param -> Text
_paramName :: Text
, Param -> Maybe Text
_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 Text (Referenced Example)
_paramExamples :: InsOrdHashMap Text (Referenced Example)
} deriving (Param -> Param -> Bool
(Param -> Param -> Bool) -> (Param -> Param -> Bool) -> Eq Param
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Param -> Param -> Bool
== :: Param -> Param -> Bool
$c/= :: Param -> Param -> Bool
/= :: Param -> Param -> Bool
Eq, Int -> Param -> ShowS
[Param] -> ShowS
Param -> FilePath
(Int -> Param -> ShowS)
-> (Param -> FilePath) -> ([Param] -> ShowS) -> Show Param
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Param -> ShowS
showsPrec :: Int -> Param -> ShowS
$cshow :: Param -> FilePath
show :: Param -> FilePath
$cshowList :: [Param] -> ShowS
showList :: [Param] -> ShowS
Show, (forall x. Param -> Rep Param x)
-> (forall x. Rep Param x -> Param) -> Generic Param
forall x. Rep Param x -> Param
forall x. Param -> Rep Param x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Param -> Rep Param x
from :: forall x. Param -> Rep Param x
$cto :: forall x. Rep Param x -> Param
to :: forall x. Rep Param x -> Param
Generic, Typeable Param
Typeable Param =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param)
-> (Param -> Constr)
-> (Param -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Param))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param))
-> ((forall b. Data b => b -> b) -> Param -> Param)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r)
-> (forall u. (forall d. Data d => d -> u) -> Param -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Param -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Param -> m Param)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param)
-> Data Param
Param -> Constr
Param -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Param -> c Param
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Param
$ctoConstr :: Param -> Constr
toConstr :: Param -> Constr
$cdataTypeOf :: Param -> DataType
dataTypeOf :: Param -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Param)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Param)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param)
$cgmapT :: (forall b. Data b => b -> b) -> Param -> Param
gmapT :: (forall b. Data b => b -> b) -> Param -> Param
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Param -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Param -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Param -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Param -> m Param
Data, Typeable)
data Example = Example
{
Example -> Maybe Text
_exampleSummary :: Maybe Text
, Example -> Maybe Text
_exampleDescription :: Maybe Text
, Example -> Maybe Value
_exampleValue :: Maybe Value
, Example -> Maybe URL
_exampleExternalValue :: Maybe URL
} deriving (Example -> Example -> Bool
(Example -> Example -> Bool)
-> (Example -> Example -> Bool) -> Eq Example
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Example -> Example -> Bool
== :: Example -> Example -> Bool
$c/= :: Example -> Example -> Bool
/= :: Example -> Example -> Bool
Eq, Int -> Example -> ShowS
[Example] -> ShowS
Example -> FilePath
(Int -> Example -> ShowS)
-> (Example -> FilePath) -> ([Example] -> ShowS) -> Show Example
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Example -> ShowS
showsPrec :: Int -> Example -> ShowS
$cshow :: Example -> FilePath
show :: Example -> FilePath
$cshowList :: [Example] -> ShowS
showList :: [Example] -> ShowS
Show, (forall x. Example -> Rep Example x)
-> (forall x. Rep Example x -> Example) -> Generic Example
forall x. Rep Example x -> Example
forall x. Example -> Rep Example x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Example -> Rep Example x
from :: forall x. Example -> Rep Example x
$cto :: forall x. Rep Example x -> Example
to :: forall x. Rep Example x -> Example
Generic, Typeable, Typeable Example
Typeable Example =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example)
-> (Example -> Constr)
-> (Example -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Example))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example))
-> ((forall b. Data b => b -> b) -> Example -> Example)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r)
-> (forall u. (forall d. Data d => d -> u) -> Example -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Example -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Example -> m Example)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example)
-> Data Example
Example -> Constr
Example -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Example -> c Example
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Example
$ctoConstr :: Example -> Constr
toConstr :: Example -> Constr
$cdataTypeOf :: Example -> DataType
dataTypeOf :: Example -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Example)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Example)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Example)
$cgmapT :: (forall b. Data b => b -> b) -> Example -> Example
gmapT :: (forall b. Data b => b -> b) -> Example -> Example
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Example -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Example -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Example -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Example -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Example -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Example -> m Example
Data)
data ExpressionOrValue
= Expression Text
| Value Value
deriving (ExpressionOrValue -> ExpressionOrValue -> Bool
(ExpressionOrValue -> ExpressionOrValue -> Bool)
-> (ExpressionOrValue -> ExpressionOrValue -> Bool)
-> Eq ExpressionOrValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpressionOrValue -> ExpressionOrValue -> Bool
== :: ExpressionOrValue -> ExpressionOrValue -> Bool
$c/= :: ExpressionOrValue -> ExpressionOrValue -> Bool
/= :: ExpressionOrValue -> ExpressionOrValue -> Bool
Eq, Int -> ExpressionOrValue -> ShowS
[ExpressionOrValue] -> ShowS
ExpressionOrValue -> FilePath
(Int -> ExpressionOrValue -> ShowS)
-> (ExpressionOrValue -> FilePath)
-> ([ExpressionOrValue] -> ShowS)
-> Show ExpressionOrValue
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpressionOrValue -> ShowS
showsPrec :: Int -> ExpressionOrValue -> ShowS
$cshow :: ExpressionOrValue -> FilePath
show :: ExpressionOrValue -> FilePath
$cshowList :: [ExpressionOrValue] -> ShowS
showList :: [ExpressionOrValue] -> ShowS
Show, (forall x. ExpressionOrValue -> Rep ExpressionOrValue x)
-> (forall x. Rep ExpressionOrValue x -> ExpressionOrValue)
-> Generic ExpressionOrValue
forall x. Rep ExpressionOrValue x -> ExpressionOrValue
forall x. ExpressionOrValue -> Rep ExpressionOrValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExpressionOrValue -> Rep ExpressionOrValue x
from :: forall x. ExpressionOrValue -> Rep ExpressionOrValue x
$cto :: forall x. Rep ExpressionOrValue x -> ExpressionOrValue
to :: forall x. Rep ExpressionOrValue x -> ExpressionOrValue
Generic, Typeable, Typeable ExpressionOrValue
Typeable ExpressionOrValue =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExpressionOrValue
-> c ExpressionOrValue)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExpressionOrValue)
-> (ExpressionOrValue -> Constr)
-> (ExpressionOrValue -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExpressionOrValue))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExpressionOrValue))
-> ((forall b. Data b => b -> b)
-> ExpressionOrValue -> ExpressionOrValue)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExpressionOrValue -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExpressionOrValue -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ExpressionOrValue -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ExpressionOrValue -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ExpressionOrValue -> m ExpressionOrValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExpressionOrValue -> m ExpressionOrValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExpressionOrValue -> m ExpressionOrValue)
-> Data ExpressionOrValue
ExpressionOrValue -> Constr
ExpressionOrValue -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExpressionOrValue -> c ExpressionOrValue
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExpressionOrValue -> c ExpressionOrValue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExpressionOrValue
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExpressionOrValue
$ctoConstr :: ExpressionOrValue -> Constr
toConstr :: ExpressionOrValue -> Constr
$cdataTypeOf :: ExpressionOrValue -> DataType
dataTypeOf :: ExpressionOrValue -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExpressionOrValue)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExpressionOrValue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExpressionOrValue)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExpressionOrValue)
$cgmapT :: (forall b. Data b => b -> b)
-> ExpressionOrValue -> ExpressionOrValue
gmapT :: (forall b. Data b => b -> b)
-> ExpressionOrValue -> ExpressionOrValue
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExpressionOrValue -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExpressionOrValue -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExpressionOrValue -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExpressionOrValue -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExpressionOrValue -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExpressionOrValue -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExpressionOrValue -> m ExpressionOrValue
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExpressionOrValue -> m ExpressionOrValue
Data)
data Link = Link
{
Link -> Maybe Text
_linkOperationRef :: Maybe Text
, Link -> Maybe Text
_linkOperationId :: Maybe Text
, Link -> InsOrdHashMap Text ExpressionOrValue
_linkParameters :: InsOrdHashMap Text ExpressionOrValue
, Link -> Maybe ExpressionOrValue
_linkRequestBody :: Maybe ExpressionOrValue
, Link -> Maybe Text
_linkDescription :: Maybe Text
, Link -> Maybe Server
_linkServer :: Maybe Server
} deriving (Link -> Link -> Bool
(Link -> Link -> Bool) -> (Link -> Link -> Bool) -> Eq Link
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Link -> Link -> Bool
== :: Link -> Link -> Bool
$c/= :: Link -> Link -> Bool
/= :: Link -> Link -> Bool
Eq, Int -> Link -> ShowS
[Link] -> ShowS
Link -> FilePath
(Int -> Link -> ShowS)
-> (Link -> FilePath) -> ([Link] -> ShowS) -> Show Link
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Link -> ShowS
showsPrec :: Int -> Link -> ShowS
$cshow :: Link -> FilePath
show :: Link -> FilePath
$cshowList :: [Link] -> ShowS
showList :: [Link] -> ShowS
Show, (forall x. Link -> Rep Link x)
-> (forall x. Rep Link x -> Link) -> Generic Link
forall x. Rep Link x -> Link
forall x. Link -> Rep Link x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Link -> Rep Link x
from :: forall x. Link -> Rep Link x
$cto :: forall x. Rep Link x -> Link
to :: forall x. Rep Link x -> Link
Generic, Typeable, Typeable Link
Typeable Link =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link)
-> (Link -> Constr)
-> (Link -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link))
-> ((forall b. Data b => b -> b) -> Link -> Link)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r)
-> (forall u. (forall d. Data d => d -> u) -> Link -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Link -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> Data Link
Link -> Constr
Link -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link
$ctoConstr :: Link -> Constr
toConstr :: Link -> Constr
$cdataTypeOf :: Link -> DataType
dataTypeOf :: Link -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link)
$cgmapT :: (forall b. Data b => b -> b) -> Link -> Link
gmapT :: (forall b. Data b => b -> b) -> Link -> Link
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
Data)
data OpenApiItems where
OpenApiItemsObject :: Referenced Schema -> OpenApiItems
OpenApiItemsArray :: [Referenced Schema] -> OpenApiItems
deriving (OpenApiItems -> OpenApiItems -> Bool
(OpenApiItems -> OpenApiItems -> Bool)
-> (OpenApiItems -> OpenApiItems -> Bool) -> Eq OpenApiItems
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenApiItems -> OpenApiItems -> Bool
== :: OpenApiItems -> OpenApiItems -> Bool
$c/= :: OpenApiItems -> OpenApiItems -> Bool
/= :: OpenApiItems -> OpenApiItems -> Bool
Eq, Int -> OpenApiItems -> ShowS
[OpenApiItems] -> ShowS
OpenApiItems -> FilePath
(Int -> OpenApiItems -> ShowS)
-> (OpenApiItems -> FilePath)
-> ([OpenApiItems] -> ShowS)
-> Show OpenApiItems
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenApiItems -> ShowS
showsPrec :: Int -> OpenApiItems -> ShowS
$cshow :: OpenApiItems -> FilePath
show :: OpenApiItems -> FilePath
$cshowList :: [OpenApiItems] -> ShowS
showList :: [OpenApiItems] -> ShowS
Show, Typeable, Typeable OpenApiItems
Typeable OpenApiItems =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems)
-> (OpenApiItems -> Constr)
-> (OpenApiItems -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiItems))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems))
-> ((forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r)
-> (forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems)
-> Data OpenApiItems
OpenApiItems -> Constr
OpenApiItems -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiItems -> c OpenApiItems
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiItems
$ctoConstr :: OpenApiItems -> Constr
toConstr :: OpenApiItems -> Constr
$cdataTypeOf :: OpenApiItems -> DataType
dataTypeOf :: OpenApiItems -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiItems)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiItems)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiItems)
$cgmapT :: (forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems
gmapT :: (forall b. Data b => b -> b) -> OpenApiItems -> OpenApiItems
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiItems -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiItems -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiItems -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiItems -> m OpenApiItems
Data)
data OpenApiType where
OpenApiString :: OpenApiType
OpenApiNumber :: OpenApiType
OpenApiInteger :: OpenApiType
OpenApiBoolean :: OpenApiType
OpenApiArray :: OpenApiType
OpenApiNull :: OpenApiType
OpenApiObject :: OpenApiType
deriving (OpenApiType -> OpenApiType -> Bool
(OpenApiType -> OpenApiType -> Bool)
-> (OpenApiType -> OpenApiType -> Bool) -> Eq OpenApiType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenApiType -> OpenApiType -> Bool
== :: OpenApiType -> OpenApiType -> Bool
$c/= :: OpenApiType -> OpenApiType -> Bool
/= :: OpenApiType -> OpenApiType -> Bool
Eq, Int -> OpenApiType -> ShowS
[OpenApiType] -> ShowS
OpenApiType -> FilePath
(Int -> OpenApiType -> ShowS)
-> (OpenApiType -> FilePath)
-> ([OpenApiType] -> ShowS)
-> Show OpenApiType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenApiType -> ShowS
showsPrec :: Int -> OpenApiType -> ShowS
$cshow :: OpenApiType -> FilePath
show :: OpenApiType -> FilePath
$cshowList :: [OpenApiType] -> ShowS
showList :: [OpenApiType] -> ShowS
Show, Typeable, (forall x. OpenApiType -> Rep OpenApiType x)
-> (forall x. Rep OpenApiType x -> OpenApiType)
-> Generic OpenApiType
forall x. Rep OpenApiType x -> OpenApiType
forall x. OpenApiType -> Rep OpenApiType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OpenApiType -> Rep OpenApiType x
from :: forall x. OpenApiType -> Rep OpenApiType x
$cto :: forall x. Rep OpenApiType x -> OpenApiType
to :: forall x. Rep OpenApiType x -> OpenApiType
Generic, Typeable OpenApiType
Typeable OpenApiType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType)
-> (OpenApiType -> Constr)
-> (OpenApiType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType))
-> ((forall b. Data b => b -> b) -> OpenApiType -> OpenApiType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r)
-> (forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType)
-> Data OpenApiType
OpenApiType -> Constr
OpenApiType -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OpenApiType -> c OpenApiType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiType
$ctoConstr :: OpenApiType -> Constr
toConstr :: OpenApiType -> Constr
$cdataTypeOf :: OpenApiType -> DataType
dataTypeOf :: OpenApiType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiType)
$cgmapT :: (forall b. Data b => b -> b) -> OpenApiType -> OpenApiType
gmapT :: (forall b. Data b => b -> b) -> OpenApiType -> OpenApiType
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OpenApiType -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OpenApiType -> m OpenApiType
Data)
data ParamLocation
=
ParamQuery
|
| ParamPath
| ParamCookie
deriving (ParamLocation -> ParamLocation -> Bool
(ParamLocation -> ParamLocation -> Bool)
-> (ParamLocation -> ParamLocation -> Bool) -> Eq ParamLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParamLocation -> ParamLocation -> Bool
== :: ParamLocation -> ParamLocation -> Bool
$c/= :: ParamLocation -> ParamLocation -> Bool
/= :: ParamLocation -> ParamLocation -> Bool
Eq, Int -> ParamLocation -> ShowS
[ParamLocation] -> ShowS
ParamLocation -> FilePath
(Int -> ParamLocation -> ShowS)
-> (ParamLocation -> FilePath)
-> ([ParamLocation] -> ShowS)
-> Show ParamLocation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamLocation -> ShowS
showsPrec :: Int -> ParamLocation -> ShowS
$cshow :: ParamLocation -> FilePath
show :: ParamLocation -> FilePath
$cshowList :: [ParamLocation] -> ShowS
showList :: [ParamLocation] -> ShowS
Show, (forall x. ParamLocation -> Rep ParamLocation x)
-> (forall x. Rep ParamLocation x -> ParamLocation)
-> Generic ParamLocation
forall x. Rep ParamLocation x -> ParamLocation
forall x. ParamLocation -> Rep ParamLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParamLocation -> Rep ParamLocation x
from :: forall x. ParamLocation -> Rep ParamLocation x
$cto :: forall x. Rep ParamLocation x -> ParamLocation
to :: forall x. Rep ParamLocation x -> ParamLocation
Generic, Typeable ParamLocation
Typeable ParamLocation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation)
-> (ParamLocation -> Constr)
-> (ParamLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation))
-> ((forall b. Data b => b -> b) -> ParamLocation -> ParamLocation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r)
-> (forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ParamLocation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation)
-> Data ParamLocation
ParamLocation -> Constr
ParamLocation -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParamLocation -> c ParamLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParamLocation
$ctoConstr :: ParamLocation -> Constr
toConstr :: ParamLocation -> Constr
$cdataTypeOf :: ParamLocation -> DataType
dataTypeOf :: ParamLocation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamLocation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParamLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParamLocation)
$cgmapT :: (forall b. Data b => b -> b) -> ParamLocation -> ParamLocation
gmapT :: (forall b. Data b => b -> b) -> ParamLocation -> ParamLocation
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParamLocation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ParamLocation -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParamLocation -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParamLocation -> m ParamLocation
Data, Typeable)
type Format = Text
type ParamName = Text
data Schema = Schema
{ Schema -> Maybe Text
_schemaTitle :: Maybe Text
, Schema -> Maybe Text
_schemaDescription :: Maybe Text
, Schema -> [Text]
_schemaRequired :: [ParamName]
, Schema -> Maybe Bool
_schemaNullable :: Maybe Bool
, Schema -> Maybe [Referenced Schema]
_schemaAllOf :: Maybe [Referenced Schema]
, Schema -> Maybe [Referenced Schema]
_schemaOneOf :: Maybe [Referenced Schema]
, Schema -> Maybe (Referenced Schema)
_schemaNot :: Maybe (Referenced Schema)
, Schema -> Maybe [Referenced Schema]
_schemaAnyOf :: Maybe [Referenced Schema]
, Schema -> InsOrdHashMap Text (Referenced Schema)
_schemaProperties :: InsOrdHashMap Text (Referenced Schema)
, Schema -> Maybe AdditionalProperties
_schemaAdditionalProperties :: Maybe AdditionalProperties
, Schema -> Maybe Discriminator
_schemaDiscriminator :: Maybe Discriminator
, Schema -> Maybe Bool
_schemaReadOnly :: Maybe Bool
, Schema -> Maybe Bool
_schemaWriteOnly :: Maybe Bool
, Schema -> Maybe Xml
_schemaXml :: Maybe Xml
, Schema -> Maybe ExternalDocs
_schemaExternalDocs :: Maybe ExternalDocs
, Schema -> Maybe Value
_schemaExample :: Maybe Value
, Schema -> Maybe Bool
_schemaDeprecated :: Maybe Bool
, Schema -> Maybe Integer
_schemaMaxProperties :: Maybe Integer
, Schema -> Maybe Integer
_schemaMinProperties :: Maybe Integer
,
Schema -> Maybe Value
_schemaDefault :: Maybe Value
, Schema -> Maybe OpenApiType
_schemaType :: Maybe OpenApiType
, Schema -> Maybe Text
_schemaFormat :: Maybe Format
, Schema -> Maybe OpenApiItems
_schemaItems :: Maybe OpenApiItems
, Schema -> Maybe Scientific
_schemaMaximum :: Maybe Scientific
, Schema -> Maybe Bool
_schemaExclusiveMaximum :: Maybe Bool
, Schema -> Maybe Scientific
_schemaMinimum :: Maybe Scientific
, Schema -> Maybe Bool
_schemaExclusiveMinimum :: Maybe Bool
, Schema -> Maybe Integer
_schemaMaxLength :: Maybe Integer
, Schema -> Maybe Integer
_schemaMinLength :: Maybe Integer
, Schema -> Maybe Text
_schemaPattern :: Maybe Pattern
, Schema -> Maybe Integer
_schemaMaxItems :: Maybe Integer
, Schema -> Maybe Integer
_schemaMinItems :: Maybe Integer
, Schema -> Maybe Bool
_schemaUniqueItems :: Maybe Bool
, Schema -> Maybe [Value]
_schemaEnum :: Maybe [Value]
, Schema -> Maybe Scientific
_schemaMultipleOf :: Maybe Scientific
} deriving (Schema -> Schema -> Bool
(Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool) -> Eq Schema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Schema -> Schema -> Bool
== :: Schema -> Schema -> Bool
$c/= :: Schema -> Schema -> Bool
/= :: Schema -> Schema -> Bool
Eq, Int -> Schema -> ShowS
[Schema] -> ShowS
Schema -> FilePath
(Int -> Schema -> ShowS)
-> (Schema -> FilePath) -> ([Schema] -> ShowS) -> Show Schema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Schema -> ShowS
showsPrec :: Int -> Schema -> ShowS
$cshow :: Schema -> FilePath
show :: Schema -> FilePath
$cshowList :: [Schema] -> ShowS
showList :: [Schema] -> ShowS
Show, (forall x. Schema -> Rep Schema x)
-> (forall x. Rep Schema x -> Schema) -> Generic Schema
forall x. Rep Schema x -> Schema
forall x. Schema -> Rep Schema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Schema -> Rep Schema x
from :: forall x. Schema -> Rep Schema x
$cto :: forall x. Rep Schema x -> Schema
to :: forall x. Rep Schema x -> Schema
Generic, Typeable Schema
Typeable Schema =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema)
-> (Schema -> Constr)
-> (Schema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Schema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema))
-> ((forall b. Data b => b -> b) -> Schema -> Schema)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Schema -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Schema -> r)
-> (forall u. (forall d. Data d => d -> u) -> Schema -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema)
-> Data Schema
Schema -> Constr
Schema -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Schema -> c Schema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Schema
$ctoConstr :: Schema -> Constr
toConstr :: Schema -> Constr
$cdataTypeOf :: Schema -> DataType
dataTypeOf :: Schema -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Schema)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Schema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema)
$cgmapT :: (forall b. Data b => b -> b) -> Schema -> Schema
gmapT :: (forall b. Data b => b -> b) -> Schema -> Schema
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Schema -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Schema -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Schema -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Schema -> m Schema
Data, Typeable)
type Pattern = Text
data Discriminator = Discriminator
{
Discriminator -> Text
_discriminatorPropertyName :: Text
, Discriminator -> InsOrdHashMap Text Text
_discriminatorMapping :: InsOrdHashMap Text Text
} deriving (Discriminator -> Discriminator -> Bool
(Discriminator -> Discriminator -> Bool)
-> (Discriminator -> Discriminator -> Bool) -> Eq Discriminator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Discriminator -> Discriminator -> Bool
== :: Discriminator -> Discriminator -> Bool
$c/= :: Discriminator -> Discriminator -> Bool
/= :: Discriminator -> Discriminator -> Bool
Eq, Int -> Discriminator -> ShowS
[Discriminator] -> ShowS
Discriminator -> FilePath
(Int -> Discriminator -> ShowS)
-> (Discriminator -> FilePath)
-> ([Discriminator] -> ShowS)
-> Show Discriminator
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Discriminator -> ShowS
showsPrec :: Int -> Discriminator -> ShowS
$cshow :: Discriminator -> FilePath
show :: Discriminator -> FilePath
$cshowList :: [Discriminator] -> ShowS
showList :: [Discriminator] -> ShowS
Show, (forall x. Discriminator -> Rep Discriminator x)
-> (forall x. Rep Discriminator x -> Discriminator)
-> Generic Discriminator
forall x. Rep Discriminator x -> Discriminator
forall x. Discriminator -> Rep Discriminator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Discriminator -> Rep Discriminator x
from :: forall x. Discriminator -> Rep Discriminator x
$cto :: forall x. Rep Discriminator x -> Discriminator
to :: forall x. Rep Discriminator x -> Discriminator
Generic, Typeable Discriminator
Typeable Discriminator =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator)
-> (Discriminator -> Constr)
-> (Discriminator -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Discriminator))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator))
-> ((forall b. Data b => b -> b) -> Discriminator -> Discriminator)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r)
-> (forall u. (forall d. Data d => d -> u) -> Discriminator -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Discriminator -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator)
-> Data Discriminator
Discriminator -> Constr
Discriminator -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Discriminator -> c Discriminator
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Discriminator
$ctoConstr :: Discriminator -> Constr
toConstr :: Discriminator -> Constr
$cdataTypeOf :: Discriminator -> DataType
dataTypeOf :: Discriminator -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Discriminator)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Discriminator)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Discriminator)
$cgmapT :: (forall b. Data b => b -> b) -> Discriminator -> Discriminator
gmapT :: (forall b. Data b => b -> b) -> Discriminator -> Discriminator
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Discriminator -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Discriminator -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Discriminator -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Discriminator -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Discriminator -> m Discriminator
Data, Typeable)
data NamedSchema = NamedSchema
{ NamedSchema -> Maybe Text
_namedSchemaName :: Maybe Text
, NamedSchema -> Schema
_namedSchemaSchema :: Schema
} deriving (NamedSchema -> NamedSchema -> Bool
(NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool) -> Eq NamedSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamedSchema -> NamedSchema -> Bool
== :: NamedSchema -> NamedSchema -> Bool
$c/= :: NamedSchema -> NamedSchema -> Bool
/= :: NamedSchema -> NamedSchema -> Bool
Eq, Int -> NamedSchema -> ShowS
[NamedSchema] -> ShowS
NamedSchema -> FilePath
(Int -> NamedSchema -> ShowS)
-> (NamedSchema -> FilePath)
-> ([NamedSchema] -> ShowS)
-> Show NamedSchema
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NamedSchema -> ShowS
showsPrec :: Int -> NamedSchema -> ShowS
$cshow :: NamedSchema -> FilePath
show :: NamedSchema -> FilePath
$cshowList :: [NamedSchema] -> ShowS
showList :: [NamedSchema] -> ShowS
Show, (forall x. NamedSchema -> Rep NamedSchema x)
-> (forall x. Rep NamedSchema x -> NamedSchema)
-> Generic NamedSchema
forall x. Rep NamedSchema x -> NamedSchema
forall x. NamedSchema -> Rep NamedSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NamedSchema -> Rep NamedSchema x
from :: forall x. NamedSchema -> Rep NamedSchema x
$cto :: forall x. Rep NamedSchema x -> NamedSchema
to :: forall x. Rep NamedSchema x -> NamedSchema
Generic, Typeable NamedSchema
Typeable NamedSchema =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema)
-> (NamedSchema -> Constr)
-> (NamedSchema -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NamedSchema))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema))
-> ((forall b. Data b => b -> b) -> NamedSchema -> NamedSchema)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r)
-> (forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NamedSchema -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema)
-> Data NamedSchema
NamedSchema -> Constr
NamedSchema -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NamedSchema -> c NamedSchema
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NamedSchema
$ctoConstr :: NamedSchema -> Constr
toConstr :: NamedSchema -> Constr
$cdataTypeOf :: NamedSchema -> DataType
dataTypeOf :: NamedSchema -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NamedSchema)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NamedSchema)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NamedSchema)
$cgmapT :: (forall b. Data b => b -> b) -> NamedSchema -> NamedSchema
gmapT :: (forall b. Data b => b -> b) -> NamedSchema -> NamedSchema
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NamedSchema -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NamedSchema -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NamedSchema -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NamedSchema -> m NamedSchema
Data, Typeable)
data Xml = Xml
{
Xml -> Maybe Text
_xmlName :: Maybe Text
, Xml -> Maybe Text
_xmlNamespace :: Maybe Text
, Xml -> Maybe Text
_xmlPrefix :: Maybe Text
, Xml -> Maybe Bool
_xmlAttribute :: Maybe Bool
, Xml -> Maybe Bool
_xmlWrapped :: Maybe Bool
} deriving (Xml -> Xml -> Bool
(Xml -> Xml -> Bool) -> (Xml -> Xml -> Bool) -> Eq Xml
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Xml -> Xml -> Bool
== :: Xml -> Xml -> Bool
$c/= :: Xml -> Xml -> Bool
/= :: Xml -> Xml -> Bool
Eq, Int -> Xml -> ShowS
[Xml] -> ShowS
Xml -> FilePath
(Int -> Xml -> ShowS)
-> (Xml -> FilePath) -> ([Xml] -> ShowS) -> Show Xml
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Xml -> ShowS
showsPrec :: Int -> Xml -> ShowS
$cshow :: Xml -> FilePath
show :: Xml -> FilePath
$cshowList :: [Xml] -> ShowS
showList :: [Xml] -> ShowS
Show, (forall x. Xml -> Rep Xml x)
-> (forall x. Rep Xml x -> Xml) -> Generic Xml
forall x. Rep Xml x -> Xml
forall x. Xml -> Rep Xml x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Xml -> Rep Xml x
from :: forall x. Xml -> Rep Xml x
$cto :: forall x. Rep Xml x -> Xml
to :: forall x. Rep Xml x -> Xml
Generic, Typeable Xml
Typeable Xml =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml)
-> (Xml -> Constr)
-> (Xml -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Xml))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml))
-> ((forall b. Data b => b -> b) -> Xml -> Xml)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r)
-> (forall u. (forall d. Data d => d -> u) -> Xml -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml)
-> Data Xml
Xml -> Constr
Xml -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Xml -> c Xml
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Xml
$ctoConstr :: Xml -> Constr
toConstr :: Xml -> Constr
$cdataTypeOf :: Xml -> DataType
dataTypeOf :: Xml -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Xml)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Xml)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xml)
$cgmapT :: (forall b. Data b => b -> b) -> Xml -> Xml
gmapT :: (forall b. Data b => b -> b) -> Xml -> Xml
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xml -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Xml -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Xml -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Xml -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m Xml
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Xml -> m 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
(Responses -> Responses -> Bool)
-> (Responses -> Responses -> Bool) -> Eq Responses
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Responses -> Responses -> Bool
== :: Responses -> Responses -> Bool
$c/= :: Responses -> Responses -> Bool
/= :: Responses -> Responses -> Bool
Eq, Int -> Responses -> ShowS
[Responses] -> ShowS
Responses -> FilePath
(Int -> Responses -> ShowS)
-> (Responses -> FilePath)
-> ([Responses] -> ShowS)
-> Show Responses
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Responses -> ShowS
showsPrec :: Int -> Responses -> ShowS
$cshow :: Responses -> FilePath
show :: Responses -> FilePath
$cshowList :: [Responses] -> ShowS
showList :: [Responses] -> ShowS
Show, (forall x. Responses -> Rep Responses x)
-> (forall x. Rep Responses x -> Responses) -> Generic Responses
forall x. Rep Responses x -> Responses
forall x. Responses -> Rep Responses x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Responses -> Rep Responses x
from :: forall x. Responses -> Rep Responses x
$cto :: forall x. Rep Responses x -> Responses
to :: forall x. Rep Responses x -> Responses
Generic, Typeable Responses
Typeable Responses =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses)
-> (Responses -> Constr)
-> (Responses -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Responses))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses))
-> ((forall b. Data b => b -> b) -> Responses -> Responses)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r)
-> (forall u. (forall d. Data d => d -> u) -> Responses -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Responses -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses)
-> Data Responses
Responses -> Constr
Responses -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Responses -> c Responses
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Responses
$ctoConstr :: Responses -> Constr
toConstr :: Responses -> Constr
$cdataTypeOf :: Responses -> DataType
dataTypeOf :: Responses -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Responses)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Responses)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Responses)
$cgmapT :: (forall b. Data b => b -> b) -> Responses -> Responses
gmapT :: (forall b. Data b => b -> b) -> Responses -> Responses
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Responses -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Responses -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Responses -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Responses -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Responses -> m Responses
Data, Typeable)
type HttpStatusCode = Int
data Response = Response
{
Response -> Text
_responseDescription :: Text
, Response -> InsOrdHashMap MediaType MediaTypeObject
_responseContent :: InsOrdHashMap MediaType MediaTypeObject
, :: InsOrdHashMap HeaderName (Referenced Header)
, Response -> InsOrdHashMap Text (Referenced Link)
_responseLinks :: InsOrdHashMap Text (Referenced Link)
} deriving (Response -> Response -> Bool
(Response -> Response -> Bool)
-> (Response -> Response -> Bool) -> Eq Response
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
/= :: Response -> Response -> Bool
Eq, Int -> Response -> ShowS
[Response] -> ShowS
Response -> FilePath
(Int -> Response -> ShowS)
-> (Response -> FilePath) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Response -> ShowS
showsPrec :: Int -> Response -> ShowS
$cshow :: Response -> FilePath
show :: Response -> FilePath
$cshowList :: [Response] -> ShowS
showList :: [Response] -> ShowS
Show, (forall x. Response -> Rep Response x)
-> (forall x. Rep Response x -> Response) -> Generic Response
forall x. Rep Response x -> Response
forall x. Response -> Rep Response x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Response -> Rep Response x
from :: forall x. Response -> Rep Response x
$cto :: forall x. Rep Response x -> Response
to :: forall x. Rep Response x -> Response
Generic, Typeable Response
Typeable Response =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response)
-> (Response -> Constr)
-> (Response -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Response))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response))
-> ((forall b. Data b => b -> b) -> Response -> Response)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r)
-> (forall u. (forall d. Data d => d -> u) -> Response -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Response -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Response -> m Response)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response)
-> Data Response
Response -> Constr
Response -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Response -> c Response
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Response
$ctoConstr :: Response -> Constr
toConstr :: Response -> Constr
$cdataTypeOf :: Response -> DataType
dataTypeOf :: Response -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Response)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Response)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response)
$cgmapT :: (forall b. Data b => b -> b) -> Response -> Response
gmapT :: (forall b. Data b => b -> b) -> Response -> Response
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Response -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Response -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Response -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Response -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Response -> m Response
Data, Typeable)
instance IsString Response where
fromString :: FilePath -> Response
fromString FilePath
s = Text
-> InsOrdHashMap MediaType MediaTypeObject
-> InsOrdHashMap Text (Referenced Header)
-> InsOrdHashMap Text (Referenced Link)
-> Response
Response (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) InsOrdHashMap MediaType MediaTypeObject
forall a. Monoid a => a
mempty InsOrdHashMap Text (Referenced Header)
forall a. Monoid a => a
mempty InsOrdHashMap Text (Referenced Link)
forall a. Monoid a => a
mempty
newtype Callback = Callback (InsOrdHashMap Text PathItem)
deriving (Callback -> Callback -> Bool
(Callback -> Callback -> Bool)
-> (Callback -> Callback -> Bool) -> Eq Callback
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Callback -> Callback -> Bool
== :: Callback -> Callback -> Bool
$c/= :: Callback -> Callback -> Bool
/= :: Callback -> Callback -> Bool
Eq, Int -> Callback -> ShowS
[Callback] -> ShowS
Callback -> FilePath
(Int -> Callback -> ShowS)
-> (Callback -> FilePath) -> ([Callback] -> ShowS) -> Show Callback
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Callback -> ShowS
showsPrec :: Int -> Callback -> ShowS
$cshow :: Callback -> FilePath
show :: Callback -> FilePath
$cshowList :: [Callback] -> ShowS
showList :: [Callback] -> ShowS
Show, (forall x. Callback -> Rep Callback x)
-> (forall x. Rep Callback x -> Callback) -> Generic Callback
forall x. Rep Callback x -> Callback
forall x. Callback -> Rep Callback x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Callback -> Rep Callback x
from :: forall x. Callback -> Rep Callback x
$cto :: forall x. Rep Callback x -> Callback
to :: forall x. Rep Callback x -> Callback
Generic, Typeable Callback
Typeable Callback =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback)
-> (Callback -> Constr)
-> (Callback -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Callback))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback))
-> ((forall b. Data b => b -> b) -> Callback -> Callback)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r)
-> (forall u. (forall d. Data d => d -> u) -> Callback -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback)
-> Data Callback
Callback -> Constr
Callback -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Callback -> c Callback
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Callback
$ctoConstr :: Callback -> Constr
toConstr :: Callback -> Constr
$cdataTypeOf :: Callback -> DataType
dataTypeOf :: Callback -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Callback)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Callback)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callback)
$cgmapT :: (forall b. Data b => b -> b) -> Callback -> Callback
gmapT :: (forall b. Data b => b -> b) -> Callback -> Callback
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Callback -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Callback -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Callback -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Callback -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m Callback
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Callback -> m 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
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
/= :: Header -> Header -> Bool
Eq, Int -> Header -> ShowS
[Header] -> ShowS
Header -> FilePath
(Int -> Header -> ShowS)
-> (Header -> FilePath) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Header -> ShowS
showsPrec :: Int -> Header -> ShowS
$cshow :: Header -> FilePath
show :: Header -> FilePath
$cshowList :: [Header] -> ShowS
showList :: [Header] -> ShowS
Show, (forall x. Header -> Rep Header x)
-> (forall x. Rep Header x -> Header) -> Generic Header
forall x. Rep Header x -> Header
forall x. Header -> Rep Header x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Header -> Rep Header x
from :: forall x. Header -> Rep Header x
$cto :: forall x. Rep Header x -> Header
to :: forall x. Rep Header x -> Header
Generic, Typeable Header
Typeable Header =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header)
-> (Header -> Constr)
-> (Header -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header))
-> ((forall b. Data b => b -> b) -> Header -> Header)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall u. (forall d. Data d => d -> u) -> Header -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Header -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> Data Header
Header -> Constr
Header -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
$ctoConstr :: Header -> Constr
toConstr :: Header -> Constr
$cdataTypeOf :: Header -> DataType
dataTypeOf :: Header -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
$cgmapT :: (forall b. Data b => b -> b) -> Header -> Header
gmapT :: (forall b. Data b => b -> b) -> Header -> Header
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
Data, Typeable)
data ApiKeyLocation
= ApiKeyQuery
|
| ApiKeyCookie
deriving (ApiKeyLocation -> ApiKeyLocation -> Bool
(ApiKeyLocation -> ApiKeyLocation -> Bool)
-> (ApiKeyLocation -> ApiKeyLocation -> Bool) -> Eq ApiKeyLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApiKeyLocation -> ApiKeyLocation -> Bool
== :: ApiKeyLocation -> ApiKeyLocation -> Bool
$c/= :: ApiKeyLocation -> ApiKeyLocation -> Bool
/= :: ApiKeyLocation -> ApiKeyLocation -> Bool
Eq, Int -> ApiKeyLocation -> ShowS
[ApiKeyLocation] -> ShowS
ApiKeyLocation -> FilePath
(Int -> ApiKeyLocation -> ShowS)
-> (ApiKeyLocation -> FilePath)
-> ([ApiKeyLocation] -> ShowS)
-> Show ApiKeyLocation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApiKeyLocation -> ShowS
showsPrec :: Int -> ApiKeyLocation -> ShowS
$cshow :: ApiKeyLocation -> FilePath
show :: ApiKeyLocation -> FilePath
$cshowList :: [ApiKeyLocation] -> ShowS
showList :: [ApiKeyLocation] -> ShowS
Show, (forall x. ApiKeyLocation -> Rep ApiKeyLocation x)
-> (forall x. Rep ApiKeyLocation x -> ApiKeyLocation)
-> Generic ApiKeyLocation
forall x. Rep ApiKeyLocation x -> ApiKeyLocation
forall x. ApiKeyLocation -> Rep ApiKeyLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ApiKeyLocation -> Rep ApiKeyLocation x
from :: forall x. ApiKeyLocation -> Rep ApiKeyLocation x
$cto :: forall x. Rep ApiKeyLocation x -> ApiKeyLocation
to :: forall x. Rep ApiKeyLocation x -> ApiKeyLocation
Generic, Typeable ApiKeyLocation
Typeable ApiKeyLocation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation)
-> (ApiKeyLocation -> Constr)
-> (ApiKeyLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation))
-> ((forall b. Data b => b -> b)
-> ApiKeyLocation -> ApiKeyLocation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ApiKeyLocation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation)
-> Data ApiKeyLocation
ApiKeyLocation -> Constr
ApiKeyLocation -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyLocation -> c ApiKeyLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyLocation
$ctoConstr :: ApiKeyLocation -> Constr
toConstr :: ApiKeyLocation -> Constr
$cdataTypeOf :: ApiKeyLocation -> DataType
dataTypeOf :: ApiKeyLocation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyLocation)
$cgmapT :: (forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation
gmapT :: (forall b. Data b => b -> b) -> ApiKeyLocation -> ApiKeyLocation
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyLocation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyLocation -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyLocation -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApiKeyLocation -> m ApiKeyLocation
Data, Typeable)
data ApiKeyParams = ApiKeyParams
{
ApiKeyParams -> Text
_apiKeyName :: Text
, ApiKeyParams -> ApiKeyLocation
_apiKeyIn :: ApiKeyLocation
} deriving (ApiKeyParams -> ApiKeyParams -> Bool
(ApiKeyParams -> ApiKeyParams -> Bool)
-> (ApiKeyParams -> ApiKeyParams -> Bool) -> Eq ApiKeyParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApiKeyParams -> ApiKeyParams -> Bool
== :: ApiKeyParams -> ApiKeyParams -> Bool
$c/= :: ApiKeyParams -> ApiKeyParams -> Bool
/= :: ApiKeyParams -> ApiKeyParams -> Bool
Eq, Int -> ApiKeyParams -> ShowS
[ApiKeyParams] -> ShowS
ApiKeyParams -> FilePath
(Int -> ApiKeyParams -> ShowS)
-> (ApiKeyParams -> FilePath)
-> ([ApiKeyParams] -> ShowS)
-> Show ApiKeyParams
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApiKeyParams -> ShowS
showsPrec :: Int -> ApiKeyParams -> ShowS
$cshow :: ApiKeyParams -> FilePath
show :: ApiKeyParams -> FilePath
$cshowList :: [ApiKeyParams] -> ShowS
showList :: [ApiKeyParams] -> ShowS
Show, (forall x. ApiKeyParams -> Rep ApiKeyParams x)
-> (forall x. Rep ApiKeyParams x -> ApiKeyParams)
-> Generic ApiKeyParams
forall x. Rep ApiKeyParams x -> ApiKeyParams
forall x. ApiKeyParams -> Rep ApiKeyParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ApiKeyParams -> Rep ApiKeyParams x
from :: forall x. ApiKeyParams -> Rep ApiKeyParams x
$cto :: forall x. Rep ApiKeyParams x -> ApiKeyParams
to :: forall x. Rep ApiKeyParams x -> ApiKeyParams
Generic, Typeable ApiKeyParams
Typeable ApiKeyParams =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams)
-> (ApiKeyParams -> Constr)
-> (ApiKeyParams -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams))
-> ((forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r)
-> (forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams)
-> Data ApiKeyParams
ApiKeyParams -> Constr
ApiKeyParams -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ApiKeyParams -> c ApiKeyParams
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ApiKeyParams
$ctoConstr :: ApiKeyParams -> Constr
toConstr :: ApiKeyParams -> Constr
$cdataTypeOf :: ApiKeyParams -> DataType
dataTypeOf :: ApiKeyParams -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ApiKeyParams)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApiKeyParams)
$cgmapT :: (forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams
gmapT :: (forall b. Data b => b -> b) -> ApiKeyParams -> ApiKeyParams
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ApiKeyParams -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ApiKeyParams -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ApiKeyParams -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ApiKeyParams -> m ApiKeyParams
Data, Typeable)
type AuthorizationURL = Text
type TokenURL = Text
newtype OAuth2ImplicitFlow
= OAuth2ImplicitFlow {OAuth2ImplicitFlow -> Text
_oAuth2ImplicitFlowAuthorizationUrl :: AuthorizationURL}
deriving (OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
(OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool)
-> (OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool)
-> Eq OAuth2ImplicitFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
== :: OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
$c/= :: OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
/= :: OAuth2ImplicitFlow -> OAuth2ImplicitFlow -> Bool
Eq, Int -> OAuth2ImplicitFlow -> ShowS
[OAuth2ImplicitFlow] -> ShowS
OAuth2ImplicitFlow -> FilePath
(Int -> OAuth2ImplicitFlow -> ShowS)
-> (OAuth2ImplicitFlow -> FilePath)
-> ([OAuth2ImplicitFlow] -> ShowS)
-> Show OAuth2ImplicitFlow
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuth2ImplicitFlow -> ShowS
showsPrec :: Int -> OAuth2ImplicitFlow -> ShowS
$cshow :: OAuth2ImplicitFlow -> FilePath
show :: OAuth2ImplicitFlow -> FilePath
$cshowList :: [OAuth2ImplicitFlow] -> ShowS
showList :: [OAuth2ImplicitFlow] -> ShowS
Show, (forall x. OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x)
-> (forall x. Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow)
-> Generic OAuth2ImplicitFlow
forall x. Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow
forall x. OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x
from :: forall x. OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x
$cto :: forall x. Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow
to :: forall x. Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow
Generic, Typeable OAuth2ImplicitFlow
Typeable OAuth2ImplicitFlow =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ImplicitFlow
-> c OAuth2ImplicitFlow)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ImplicitFlow)
-> (OAuth2ImplicitFlow -> Constr)
-> (OAuth2ImplicitFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2ImplicitFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ImplicitFlow))
-> ((forall b. Data b => b -> b)
-> OAuth2ImplicitFlow -> OAuth2ImplicitFlow)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2ImplicitFlow -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2ImplicitFlow -> r)
-> (forall u.
(forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OAuth2ImplicitFlow -> m OAuth2ImplicitFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ImplicitFlow -> m OAuth2ImplicitFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ImplicitFlow -> m OAuth2ImplicitFlow)
-> Data OAuth2ImplicitFlow
OAuth2ImplicitFlow -> Constr
OAuth2ImplicitFlow -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ImplicitFlow
-> c OAuth2ImplicitFlow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ImplicitFlow
-> c OAuth2ImplicitFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ImplicitFlow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ImplicitFlow
$ctoConstr :: OAuth2ImplicitFlow -> Constr
toConstr :: OAuth2ImplicitFlow -> Constr
$cdataTypeOf :: OAuth2ImplicitFlow -> DataType
dataTypeOf :: OAuth2ImplicitFlow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2ImplicitFlow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2ImplicitFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ImplicitFlow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ImplicitFlow)
$cgmapT :: (forall b. Data b => b -> b)
-> OAuth2ImplicitFlow -> OAuth2ImplicitFlow
gmapT :: (forall b. Data b => b -> b)
-> OAuth2ImplicitFlow -> OAuth2ImplicitFlow
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2ImplicitFlow -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2ImplicitFlow -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2ImplicitFlow -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ImplicitFlow -> m OAuth2ImplicitFlow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ImplicitFlow -> m OAuth2ImplicitFlow
Data, Typeable)
newtype OAuth2PasswordFlow
= OAuth2PasswordFlow {OAuth2PasswordFlow -> Text
_oAuth2PasswordFlowTokenUrl :: TokenURL}
deriving (OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
(OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool)
-> (OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool)
-> Eq OAuth2PasswordFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
== :: OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
$c/= :: OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
/= :: OAuth2PasswordFlow -> OAuth2PasswordFlow -> Bool
Eq, Int -> OAuth2PasswordFlow -> ShowS
[OAuth2PasswordFlow] -> ShowS
OAuth2PasswordFlow -> FilePath
(Int -> OAuth2PasswordFlow -> ShowS)
-> (OAuth2PasswordFlow -> FilePath)
-> ([OAuth2PasswordFlow] -> ShowS)
-> Show OAuth2PasswordFlow
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuth2PasswordFlow -> ShowS
showsPrec :: Int -> OAuth2PasswordFlow -> ShowS
$cshow :: OAuth2PasswordFlow -> FilePath
show :: OAuth2PasswordFlow -> FilePath
$cshowList :: [OAuth2PasswordFlow] -> ShowS
showList :: [OAuth2PasswordFlow] -> ShowS
Show, (forall x. OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x)
-> (forall x. Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow)
-> Generic OAuth2PasswordFlow
forall x. Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow
forall x. OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x
from :: forall x. OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x
$cto :: forall x. Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow
to :: forall x. Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow
Generic, Typeable OAuth2PasswordFlow
Typeable OAuth2PasswordFlow =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2PasswordFlow
-> c OAuth2PasswordFlow)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2PasswordFlow)
-> (OAuth2PasswordFlow -> Constr)
-> (OAuth2PasswordFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2PasswordFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2PasswordFlow))
-> ((forall b. Data b => b -> b)
-> OAuth2PasswordFlow -> OAuth2PasswordFlow)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2PasswordFlow -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2PasswordFlow -> r)
-> (forall u.
(forall d. Data d => d -> u) -> OAuth2PasswordFlow -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OAuth2PasswordFlow -> m OAuth2PasswordFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2PasswordFlow -> m OAuth2PasswordFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2PasswordFlow -> m OAuth2PasswordFlow)
-> Data OAuth2PasswordFlow
OAuth2PasswordFlow -> Constr
OAuth2PasswordFlow -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2PasswordFlow
-> c OAuth2PasswordFlow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2PasswordFlow
-> c OAuth2PasswordFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2PasswordFlow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2PasswordFlow
$ctoConstr :: OAuth2PasswordFlow -> Constr
toConstr :: OAuth2PasswordFlow -> Constr
$cdataTypeOf :: OAuth2PasswordFlow -> DataType
dataTypeOf :: OAuth2PasswordFlow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2PasswordFlow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2PasswordFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2PasswordFlow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2PasswordFlow)
$cgmapT :: (forall b. Data b => b -> b)
-> OAuth2PasswordFlow -> OAuth2PasswordFlow
gmapT :: (forall b. Data b => b -> b)
-> OAuth2PasswordFlow -> OAuth2PasswordFlow
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2PasswordFlow -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2PasswordFlow -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2PasswordFlow -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2PasswordFlow -> m OAuth2PasswordFlow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2PasswordFlow -> m OAuth2PasswordFlow
Data, Typeable)
newtype OAuth2ClientCredentialsFlow
= OAuth2ClientCredentialsFlow {OAuth2ClientCredentialsFlow -> Text
_oAuth2ClientCredentialsFlowTokenUrl :: TokenURL}
deriving (OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
(OAuth2ClientCredentialsFlow
-> OAuth2ClientCredentialsFlow -> Bool)
-> (OAuth2ClientCredentialsFlow
-> OAuth2ClientCredentialsFlow -> Bool)
-> Eq OAuth2ClientCredentialsFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
== :: OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
$c/= :: OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
/= :: OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow -> Bool
Eq, Int -> OAuth2ClientCredentialsFlow -> ShowS
[OAuth2ClientCredentialsFlow] -> ShowS
OAuth2ClientCredentialsFlow -> FilePath
(Int -> OAuth2ClientCredentialsFlow -> ShowS)
-> (OAuth2ClientCredentialsFlow -> FilePath)
-> ([OAuth2ClientCredentialsFlow] -> ShowS)
-> Show OAuth2ClientCredentialsFlow
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuth2ClientCredentialsFlow -> ShowS
showsPrec :: Int -> OAuth2ClientCredentialsFlow -> ShowS
$cshow :: OAuth2ClientCredentialsFlow -> FilePath
show :: OAuth2ClientCredentialsFlow -> FilePath
$cshowList :: [OAuth2ClientCredentialsFlow] -> ShowS
showList :: [OAuth2ClientCredentialsFlow] -> ShowS
Show, (forall x.
OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x)
-> (forall x.
Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow)
-> Generic OAuth2ClientCredentialsFlow
forall x.
Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow
forall x.
OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x
from :: forall x.
OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x
$cto :: forall x.
Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow
to :: forall x.
Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow
Generic, Typeable OAuth2ClientCredentialsFlow
Typeable OAuth2ClientCredentialsFlow =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ClientCredentialsFlow
-> c OAuth2ClientCredentialsFlow)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ClientCredentialsFlow)
-> (OAuth2ClientCredentialsFlow -> Constr)
-> (OAuth2ClientCredentialsFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2ClientCredentialsFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ClientCredentialsFlow))
-> ((forall b. Data b => b -> b)
-> OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2ClientCredentialsFlow
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2ClientCredentialsFlow
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u)
-> OAuth2ClientCredentialsFlow
-> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OAuth2ClientCredentialsFlow -> m OAuth2ClientCredentialsFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ClientCredentialsFlow -> m OAuth2ClientCredentialsFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ClientCredentialsFlow -> m OAuth2ClientCredentialsFlow)
-> Data OAuth2ClientCredentialsFlow
OAuth2ClientCredentialsFlow -> Constr
OAuth2ClientCredentialsFlow -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ClientCredentialsFlow
-> c OAuth2ClientCredentialsFlow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2ClientCredentialsFlow
-> c OAuth2ClientCredentialsFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ClientCredentialsFlow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2ClientCredentialsFlow
$ctoConstr :: OAuth2ClientCredentialsFlow -> Constr
toConstr :: OAuth2ClientCredentialsFlow -> Constr
$cdataTypeOf :: OAuth2ClientCredentialsFlow -> DataType
dataTypeOf :: OAuth2ClientCredentialsFlow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2ClientCredentialsFlow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2ClientCredentialsFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ClientCredentialsFlow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2ClientCredentialsFlow)
$cgmapT :: (forall b. Data b => b -> b)
-> OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow
gmapT :: (forall b. Data b => b -> b)
-> OAuth2ClientCredentialsFlow -> OAuth2ClientCredentialsFlow
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2ClientCredentialsFlow
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2ClientCredentialsFlow
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2ClientCredentialsFlow -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ClientCredentialsFlow -> m OAuth2ClientCredentialsFlow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2ClientCredentialsFlow -> m OAuth2ClientCredentialsFlow
Data, Typeable)
data OAuth2AuthorizationCodeFlow = OAuth2AuthorizationCodeFlow
{ OAuth2AuthorizationCodeFlow -> Text
_oAuth2AuthorizationCodeFlowAuthorizationUrl :: AuthorizationURL
, OAuth2AuthorizationCodeFlow -> Text
_oAuth2AuthorizationCodeFlowTokenUrl :: TokenURL
} deriving (OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
(OAuth2AuthorizationCodeFlow
-> OAuth2AuthorizationCodeFlow -> Bool)
-> (OAuth2AuthorizationCodeFlow
-> OAuth2AuthorizationCodeFlow -> Bool)
-> Eq OAuth2AuthorizationCodeFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
== :: OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
$c/= :: OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
/= :: OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow -> Bool
Eq, Int -> OAuth2AuthorizationCodeFlow -> ShowS
[OAuth2AuthorizationCodeFlow] -> ShowS
OAuth2AuthorizationCodeFlow -> FilePath
(Int -> OAuth2AuthorizationCodeFlow -> ShowS)
-> (OAuth2AuthorizationCodeFlow -> FilePath)
-> ([OAuth2AuthorizationCodeFlow] -> ShowS)
-> Show OAuth2AuthorizationCodeFlow
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuth2AuthorizationCodeFlow -> ShowS
showsPrec :: Int -> OAuth2AuthorizationCodeFlow -> ShowS
$cshow :: OAuth2AuthorizationCodeFlow -> FilePath
show :: OAuth2AuthorizationCodeFlow -> FilePath
$cshowList :: [OAuth2AuthorizationCodeFlow] -> ShowS
showList :: [OAuth2AuthorizationCodeFlow] -> ShowS
Show, (forall x.
OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x)
-> (forall x.
Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow)
-> Generic OAuth2AuthorizationCodeFlow
forall x.
Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow
forall x.
OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x
from :: forall x.
OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x
$cto :: forall x.
Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow
to :: forall x.
Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow
Generic, Typeable OAuth2AuthorizationCodeFlow
Typeable OAuth2AuthorizationCodeFlow =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2AuthorizationCodeFlow
-> c OAuth2AuthorizationCodeFlow)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2AuthorizationCodeFlow)
-> (OAuth2AuthorizationCodeFlow -> Constr)
-> (OAuth2AuthorizationCodeFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2AuthorizationCodeFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2AuthorizationCodeFlow))
-> ((forall b. Data b => b -> b)
-> OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2AuthorizationCodeFlow
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2AuthorizationCodeFlow
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u)
-> OAuth2AuthorizationCodeFlow
-> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OAuth2AuthorizationCodeFlow -> m OAuth2AuthorizationCodeFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2AuthorizationCodeFlow -> m OAuth2AuthorizationCodeFlow)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2AuthorizationCodeFlow -> m OAuth2AuthorizationCodeFlow)
-> Data OAuth2AuthorizationCodeFlow
OAuth2AuthorizationCodeFlow -> Constr
OAuth2AuthorizationCodeFlow -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2AuthorizationCodeFlow
-> c OAuth2AuthorizationCodeFlow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OAuth2AuthorizationCodeFlow
-> c OAuth2AuthorizationCodeFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2AuthorizationCodeFlow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2AuthorizationCodeFlow
$ctoConstr :: OAuth2AuthorizationCodeFlow -> Constr
toConstr :: OAuth2AuthorizationCodeFlow -> Constr
$cdataTypeOf :: OAuth2AuthorizationCodeFlow -> DataType
dataTypeOf :: OAuth2AuthorizationCodeFlow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2AuthorizationCodeFlow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c OAuth2AuthorizationCodeFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2AuthorizationCodeFlow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2AuthorizationCodeFlow)
$cgmapT :: (forall b. Data b => b -> b)
-> OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow
gmapT :: (forall b. Data b => b -> b)
-> OAuth2AuthorizationCodeFlow -> OAuth2AuthorizationCodeFlow
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2AuthorizationCodeFlow
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OAuth2AuthorizationCodeFlow
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> OAuth2AuthorizationCodeFlow -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2AuthorizationCodeFlow -> m OAuth2AuthorizationCodeFlow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OAuth2AuthorizationCodeFlow -> m 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 Text Text
_oAuth2Scopes :: InsOrdHashMap Text Text
} deriving (OAuth2Flow p -> OAuth2Flow p -> Bool
(OAuth2Flow p -> OAuth2Flow p -> Bool)
-> (OAuth2Flow p -> OAuth2Flow p -> Bool) -> Eq (OAuth2Flow p)
forall p. Eq p => OAuth2Flow p -> OAuth2Flow p -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$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
/= :: OAuth2Flow p -> OAuth2Flow p -> Bool
Eq, Int -> OAuth2Flow p -> ShowS
[OAuth2Flow p] -> ShowS
OAuth2Flow p -> FilePath
(Int -> OAuth2Flow p -> ShowS)
-> (OAuth2Flow p -> FilePath)
-> ([OAuth2Flow p] -> ShowS)
-> Show (OAuth2Flow p)
forall p. Show p => Int -> OAuth2Flow p -> ShowS
forall p. Show p => [OAuth2Flow p] -> ShowS
forall p. Show p => OAuth2Flow p -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall p. Show p => Int -> OAuth2Flow p -> ShowS
showsPrec :: Int -> OAuth2Flow p -> ShowS
$cshow :: forall p. Show p => OAuth2Flow p -> FilePath
show :: OAuth2Flow p -> FilePath
$cshowList :: forall p. Show p => [OAuth2Flow p] -> ShowS
showList :: [OAuth2Flow p] -> ShowS
Show, (forall x. OAuth2Flow p -> Rep (OAuth2Flow p) x)
-> (forall x. Rep (OAuth2Flow p) x -> OAuth2Flow p)
-> Generic (OAuth2Flow p)
forall x. Rep (OAuth2Flow p) x -> OAuth2Flow p
forall x. OAuth2Flow p -> Rep (OAuth2Flow p) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p x. Rep (OAuth2Flow p) x -> OAuth2Flow p
forall p x. OAuth2Flow p -> Rep (OAuth2Flow p) x
$cfrom :: forall p x. OAuth2Flow p -> Rep (OAuth2Flow p) x
from :: forall x. OAuth2Flow p -> Rep (OAuth2Flow p) x
$cto :: forall p x. Rep (OAuth2Flow p) x -> OAuth2Flow p
to :: forall x. Rep (OAuth2Flow p) x -> OAuth2Flow p
Generic, Typeable (OAuth2Flow p)
Typeable (OAuth2Flow p) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p))
-> (OAuth2Flow p -> Constr)
-> (OAuth2Flow p -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p)))
-> ((forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r)
-> (forall u. (forall d. Data d => d -> u) -> OAuth2Flow p -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p))
-> Data (OAuth2Flow p)
OAuth2Flow p -> Constr
OAuth2Flow p -> DataType
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
forall p. Data p => Typeable (OAuth2Flow p)
forall p. Data p => OAuth2Flow p -> Constr
forall p. Data p => OAuth2Flow p -> DataType
forall p.
Data p =>
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
forall p u.
Data p =>
Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
forall p u.
Data p =>
(forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
forall p r r'.
Data p =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall p r r'.
Data p =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall p (m :: * -> *).
(Data p, Monad m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall p (m :: * -> *).
(Data p, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall p (c :: * -> *).
Data p =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
forall p (c :: * -> *).
Data p =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
forall p (t :: * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
forall p (t :: * -> * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
forall u. (forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> c (OAuth2Flow p)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
$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)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flow p -> 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)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OAuth2Flow p)
$ctoConstr :: forall p. Data p => OAuth2Flow p -> Constr
toConstr :: OAuth2Flow p -> Constr
$cdataTypeOf :: forall p. Data p => OAuth2Flow p -> DataType
dataTypeOf :: OAuth2Flow p -> DataType
$cdataCast1 :: forall p (t :: * -> *) (c :: * -> *).
(Data p, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OAuth2Flow p))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> 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))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OAuth2Flow p))
$cgmapT :: forall p.
Data p =>
(forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
gmapT :: (forall b. Data b => b -> b) -> OAuth2Flow p -> OAuth2Flow p
$cgmapQl :: 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
$cgmapQr :: forall p r r'.
Data p =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flow p -> r
$cgmapQ :: forall p u.
Data p =>
(forall d. Data d => d -> u) -> OAuth2Flow p -> [u]
gmapQ :: forall u. (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
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flow p -> u
$cgmapM :: forall p (m :: * -> *).
(Data p, Monad 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)
$cgmapMp :: 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)
$cgmapMo :: forall p (m :: * -> *).
(Data p, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (OAuth2Flow p)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flow p -> m (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
(OAuth2Flows -> OAuth2Flows -> Bool)
-> (OAuth2Flows -> OAuth2Flows -> Bool) -> Eq OAuth2Flows
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuth2Flows -> OAuth2Flows -> Bool
== :: OAuth2Flows -> OAuth2Flows -> Bool
$c/= :: OAuth2Flows -> OAuth2Flows -> Bool
/= :: OAuth2Flows -> OAuth2Flows -> Bool
Eq, Int -> OAuth2Flows -> ShowS
[OAuth2Flows] -> ShowS
OAuth2Flows -> FilePath
(Int -> OAuth2Flows -> ShowS)
-> (OAuth2Flows -> FilePath)
-> ([OAuth2Flows] -> ShowS)
-> Show OAuth2Flows
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuth2Flows -> ShowS
showsPrec :: Int -> OAuth2Flows -> ShowS
$cshow :: OAuth2Flows -> FilePath
show :: OAuth2Flows -> FilePath
$cshowList :: [OAuth2Flows] -> ShowS
showList :: [OAuth2Flows] -> ShowS
Show, (forall x. OAuth2Flows -> Rep OAuth2Flows x)
-> (forall x. Rep OAuth2Flows x -> OAuth2Flows)
-> Generic OAuth2Flows
forall x. Rep OAuth2Flows x -> OAuth2Flows
forall x. OAuth2Flows -> Rep OAuth2Flows x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OAuth2Flows -> Rep OAuth2Flows x
from :: forall x. OAuth2Flows -> Rep OAuth2Flows x
$cto :: forall x. Rep OAuth2Flows x -> OAuth2Flows
to :: forall x. Rep OAuth2Flows x -> OAuth2Flows
Generic, Typeable OAuth2Flows
Typeable OAuth2Flows =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flows -> c OAuth2Flows)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flows)
-> (OAuth2Flows -> Constr)
-> (OAuth2Flows -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Flows))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Flows))
-> ((forall b. Data b => b -> b) -> OAuth2Flows -> OAuth2Flows)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flows -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flows -> r)
-> (forall u. (forall d. Data d => d -> u) -> OAuth2Flows -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OAuth2Flows -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OAuth2Flows -> m OAuth2Flows)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flows -> m OAuth2Flows)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flows -> m OAuth2Flows)
-> Data OAuth2Flows
OAuth2Flows -> Constr
OAuth2Flows -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flows -> c OAuth2Flows
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OAuth2Flows -> c OAuth2Flows
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flows
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OAuth2Flows
$ctoConstr :: OAuth2Flows -> Constr
toConstr :: OAuth2Flows -> Constr
$cdataTypeOf :: OAuth2Flows -> DataType
dataTypeOf :: OAuth2Flows -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Flows)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OAuth2Flows)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Flows)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OAuth2Flows)
$cgmapT :: (forall b. Data b => b -> b) -> OAuth2Flows -> OAuth2Flows
gmapT :: (forall b. Data b => b -> b) -> OAuth2Flows -> OAuth2Flows
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flows -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OAuth2Flows -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Flows -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OAuth2Flows -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flows -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OAuth2Flows -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flows -> m OAuth2Flows
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OAuth2Flows -> m OAuth2Flows
Data, Typeable)
type BearerFormat = Text
data HttpSchemeType
= HttpSchemeBearer (Maybe BearerFormat)
| HttpSchemeBasic
| HttpSchemeCustom Text
deriving (HttpSchemeType -> HttpSchemeType -> Bool
(HttpSchemeType -> HttpSchemeType -> Bool)
-> (HttpSchemeType -> HttpSchemeType -> Bool) -> Eq HttpSchemeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HttpSchemeType -> HttpSchemeType -> Bool
== :: HttpSchemeType -> HttpSchemeType -> Bool
$c/= :: HttpSchemeType -> HttpSchemeType -> Bool
/= :: HttpSchemeType -> HttpSchemeType -> Bool
Eq, Int -> HttpSchemeType -> ShowS
[HttpSchemeType] -> ShowS
HttpSchemeType -> FilePath
(Int -> HttpSchemeType -> ShowS)
-> (HttpSchemeType -> FilePath)
-> ([HttpSchemeType] -> ShowS)
-> Show HttpSchemeType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HttpSchemeType -> ShowS
showsPrec :: Int -> HttpSchemeType -> ShowS
$cshow :: HttpSchemeType -> FilePath
show :: HttpSchemeType -> FilePath
$cshowList :: [HttpSchemeType] -> ShowS
showList :: [HttpSchemeType] -> ShowS
Show, (forall x. HttpSchemeType -> Rep HttpSchemeType x)
-> (forall x. Rep HttpSchemeType x -> HttpSchemeType)
-> Generic HttpSchemeType
forall x. Rep HttpSchemeType x -> HttpSchemeType
forall x. HttpSchemeType -> Rep HttpSchemeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HttpSchemeType -> Rep HttpSchemeType x
from :: forall x. HttpSchemeType -> Rep HttpSchemeType x
$cto :: forall x. Rep HttpSchemeType x -> HttpSchemeType
to :: forall x. Rep HttpSchemeType x -> HttpSchemeType
Generic, Typeable HttpSchemeType
Typeable HttpSchemeType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HttpSchemeType -> c HttpSchemeType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HttpSchemeType)
-> (HttpSchemeType -> Constr)
-> (HttpSchemeType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HttpSchemeType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HttpSchemeType))
-> ((forall b. Data b => b -> b)
-> HttpSchemeType -> HttpSchemeType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HttpSchemeType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HttpSchemeType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> HttpSchemeType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HttpSchemeType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HttpSchemeType -> m HttpSchemeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HttpSchemeType -> m HttpSchemeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HttpSchemeType -> m HttpSchemeType)
-> Data HttpSchemeType
HttpSchemeType -> Constr
HttpSchemeType -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HttpSchemeType -> c HttpSchemeType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HttpSchemeType -> c HttpSchemeType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HttpSchemeType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HttpSchemeType
$ctoConstr :: HttpSchemeType -> Constr
toConstr :: HttpSchemeType -> Constr
$cdataTypeOf :: HttpSchemeType -> DataType
dataTypeOf :: HttpSchemeType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HttpSchemeType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HttpSchemeType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HttpSchemeType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HttpSchemeType)
$cgmapT :: (forall b. Data b => b -> b) -> HttpSchemeType -> HttpSchemeType
gmapT :: (forall b. Data b => b -> b) -> HttpSchemeType -> HttpSchemeType
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HttpSchemeType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HttpSchemeType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HttpSchemeType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HttpSchemeType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HttpSchemeType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HttpSchemeType -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HttpSchemeType -> m HttpSchemeType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HttpSchemeType -> m HttpSchemeType
Data, Typeable)
data SecuritySchemeType
= SecuritySchemeHttp HttpSchemeType
| SecuritySchemeApiKey ApiKeyParams
| SecuritySchemeOAuth2 OAuth2Flows
| SecuritySchemeOpenIdConnect URL
deriving (SecuritySchemeType -> SecuritySchemeType -> Bool
(SecuritySchemeType -> SecuritySchemeType -> Bool)
-> (SecuritySchemeType -> SecuritySchemeType -> Bool)
-> Eq SecuritySchemeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SecuritySchemeType -> SecuritySchemeType -> Bool
== :: SecuritySchemeType -> SecuritySchemeType -> Bool
$c/= :: SecuritySchemeType -> SecuritySchemeType -> Bool
/= :: SecuritySchemeType -> SecuritySchemeType -> Bool
Eq, Int -> SecuritySchemeType -> ShowS
[SecuritySchemeType] -> ShowS
SecuritySchemeType -> FilePath
(Int -> SecuritySchemeType -> ShowS)
-> (SecuritySchemeType -> FilePath)
-> ([SecuritySchemeType] -> ShowS)
-> Show SecuritySchemeType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SecuritySchemeType -> ShowS
showsPrec :: Int -> SecuritySchemeType -> ShowS
$cshow :: SecuritySchemeType -> FilePath
show :: SecuritySchemeType -> FilePath
$cshowList :: [SecuritySchemeType] -> ShowS
showList :: [SecuritySchemeType] -> ShowS
Show, (forall x. SecuritySchemeType -> Rep SecuritySchemeType x)
-> (forall x. Rep SecuritySchemeType x -> SecuritySchemeType)
-> Generic SecuritySchemeType
forall x. Rep SecuritySchemeType x -> SecuritySchemeType
forall x. SecuritySchemeType -> Rep SecuritySchemeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SecuritySchemeType -> Rep SecuritySchemeType x
from :: forall x. SecuritySchemeType -> Rep SecuritySchemeType x
$cto :: forall x. Rep SecuritySchemeType x -> SecuritySchemeType
to :: forall x. Rep SecuritySchemeType x -> SecuritySchemeType
Generic, Typeable SecuritySchemeType
Typeable SecuritySchemeType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType)
-> (SecuritySchemeType -> Constr)
-> (SecuritySchemeType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType))
-> ((forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SecuritySchemeType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType)
-> Data SecuritySchemeType
SecuritySchemeType -> Constr
SecuritySchemeType -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecuritySchemeType
-> c SecuritySchemeType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecuritySchemeType
$ctoConstr :: SecuritySchemeType -> Constr
toConstr :: SecuritySchemeType -> Constr
$cdataTypeOf :: SecuritySchemeType -> DataType
dataTypeOf :: SecuritySchemeType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecuritySchemeType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecuritySchemeType)
$cgmapT :: (forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType
gmapT :: (forall b. Data b => b -> b)
-> SecuritySchemeType -> SecuritySchemeType
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecuritySchemeType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SecuritySchemeType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecuritySchemeType -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecuritySchemeType -> m SecuritySchemeType
Data, Typeable)
data SecurityScheme = SecurityScheme
{
SecurityScheme -> SecuritySchemeType
_securitySchemeType :: SecuritySchemeType
, SecurityScheme -> Maybe Text
_securitySchemeDescription :: Maybe Text
} deriving (SecurityScheme -> SecurityScheme -> Bool
(SecurityScheme -> SecurityScheme -> Bool)
-> (SecurityScheme -> SecurityScheme -> Bool) -> Eq SecurityScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SecurityScheme -> SecurityScheme -> Bool
== :: SecurityScheme -> SecurityScheme -> Bool
$c/= :: SecurityScheme -> SecurityScheme -> Bool
/= :: SecurityScheme -> SecurityScheme -> Bool
Eq, Int -> SecurityScheme -> ShowS
[SecurityScheme] -> ShowS
SecurityScheme -> FilePath
(Int -> SecurityScheme -> ShowS)
-> (SecurityScheme -> FilePath)
-> ([SecurityScheme] -> ShowS)
-> Show SecurityScheme
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SecurityScheme -> ShowS
showsPrec :: Int -> SecurityScheme -> ShowS
$cshow :: SecurityScheme -> FilePath
show :: SecurityScheme -> FilePath
$cshowList :: [SecurityScheme] -> ShowS
showList :: [SecurityScheme] -> ShowS
Show, (forall x. SecurityScheme -> Rep SecurityScheme x)
-> (forall x. Rep SecurityScheme x -> SecurityScheme)
-> Generic SecurityScheme
forall x. Rep SecurityScheme x -> SecurityScheme
forall x. SecurityScheme -> Rep SecurityScheme x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SecurityScheme -> Rep SecurityScheme x
from :: forall x. SecurityScheme -> Rep SecurityScheme x
$cto :: forall x. Rep SecurityScheme x -> SecurityScheme
to :: forall x. Rep SecurityScheme x -> SecurityScheme
Generic, Typeable SecurityScheme
Typeable SecurityScheme =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme)
-> (SecurityScheme -> Constr)
-> (SecurityScheme -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityScheme))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme))
-> ((forall b. Data b => b -> b)
-> SecurityScheme -> SecurityScheme)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SecurityScheme -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme)
-> Data SecurityScheme
SecurityScheme -> Constr
SecurityScheme -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SecurityScheme -> c SecurityScheme
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityScheme
$ctoConstr :: SecurityScheme -> Constr
toConstr :: SecurityScheme -> Constr
$cdataTypeOf :: SecurityScheme -> DataType
dataTypeOf :: SecurityScheme -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityScheme)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityScheme)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityScheme)
$cgmapT :: (forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme
gmapT :: (forall b. Data b => b -> b) -> SecurityScheme -> SecurityScheme
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityScheme -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SecurityScheme -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityScheme -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityScheme -> m SecurityScheme
Data, Typeable)
newtype SecurityDefinitions
= SecurityDefinitions (Definitions SecurityScheme)
deriving (SecurityDefinitions -> SecurityDefinitions -> Bool
(SecurityDefinitions -> SecurityDefinitions -> Bool)
-> (SecurityDefinitions -> SecurityDefinitions -> Bool)
-> Eq SecurityDefinitions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SecurityDefinitions -> SecurityDefinitions -> Bool
== :: SecurityDefinitions -> SecurityDefinitions -> Bool
$c/= :: SecurityDefinitions -> SecurityDefinitions -> Bool
/= :: SecurityDefinitions -> SecurityDefinitions -> Bool
Eq, Int -> SecurityDefinitions -> ShowS
[SecurityDefinitions] -> ShowS
SecurityDefinitions -> FilePath
(Int -> SecurityDefinitions -> ShowS)
-> (SecurityDefinitions -> FilePath)
-> ([SecurityDefinitions] -> ShowS)
-> Show SecurityDefinitions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SecurityDefinitions -> ShowS
showsPrec :: Int -> SecurityDefinitions -> ShowS
$cshow :: SecurityDefinitions -> FilePath
show :: SecurityDefinitions -> FilePath
$cshowList :: [SecurityDefinitions] -> ShowS
showList :: [SecurityDefinitions] -> ShowS
Show, (forall x. SecurityDefinitions -> Rep SecurityDefinitions x)
-> (forall x. Rep SecurityDefinitions x -> SecurityDefinitions)
-> Generic SecurityDefinitions
forall x. Rep SecurityDefinitions x -> SecurityDefinitions
forall x. SecurityDefinitions -> Rep SecurityDefinitions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SecurityDefinitions -> Rep SecurityDefinitions x
from :: forall x. SecurityDefinitions -> Rep SecurityDefinitions x
$cto :: forall x. Rep SecurityDefinitions x -> SecurityDefinitions
to :: forall x. Rep SecurityDefinitions x -> SecurityDefinitions
Generic, Typeable SecurityDefinitions
Typeable SecurityDefinitions =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions)
-> (SecurityDefinitions -> Constr)
-> (SecurityDefinitions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions))
-> ((forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions)
-> Data SecurityDefinitions
SecurityDefinitions -> Constr
SecurityDefinitions -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityDefinitions
-> c SecurityDefinitions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityDefinitions
$ctoConstr :: SecurityDefinitions -> Constr
toConstr :: SecurityDefinitions -> Constr
$cdataTypeOf :: SecurityDefinitions -> DataType
dataTypeOf :: SecurityDefinitions -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityDefinitions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityDefinitions)
$cgmapT :: (forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions
gmapT :: (forall b. Data b => b -> b)
-> SecurityDefinitions -> SecurityDefinitions
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityDefinitions -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityDefinitions -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityDefinitions -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityDefinitions -> m SecurityDefinitions
Data, Typeable)
newtype SecurityRequirement = SecurityRequirement
{ SecurityRequirement -> InsOrdHashMap Text [Text]
getSecurityRequirement :: InsOrdHashMap Text [Text]
} deriving (SecurityRequirement -> SecurityRequirement -> Bool
(SecurityRequirement -> SecurityRequirement -> Bool)
-> (SecurityRequirement -> SecurityRequirement -> Bool)
-> Eq SecurityRequirement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SecurityRequirement -> SecurityRequirement -> Bool
== :: SecurityRequirement -> SecurityRequirement -> Bool
$c/= :: SecurityRequirement -> SecurityRequirement -> Bool
/= :: SecurityRequirement -> SecurityRequirement -> Bool
Eq, ReadPrec [SecurityRequirement]
ReadPrec SecurityRequirement
Int -> ReadS SecurityRequirement
ReadS [SecurityRequirement]
(Int -> ReadS SecurityRequirement)
-> ReadS [SecurityRequirement]
-> ReadPrec SecurityRequirement
-> ReadPrec [SecurityRequirement]
-> Read SecurityRequirement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SecurityRequirement
readsPrec :: Int -> ReadS SecurityRequirement
$creadList :: ReadS [SecurityRequirement]
readList :: ReadS [SecurityRequirement]
$creadPrec :: ReadPrec SecurityRequirement
readPrec :: ReadPrec SecurityRequirement
$creadListPrec :: ReadPrec [SecurityRequirement]
readListPrec :: ReadPrec [SecurityRequirement]
Read, Int -> SecurityRequirement -> ShowS
[SecurityRequirement] -> ShowS
SecurityRequirement -> FilePath
(Int -> SecurityRequirement -> ShowS)
-> (SecurityRequirement -> FilePath)
-> ([SecurityRequirement] -> ShowS)
-> Show SecurityRequirement
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SecurityRequirement -> ShowS
showsPrec :: Int -> SecurityRequirement -> ShowS
$cshow :: SecurityRequirement -> FilePath
show :: SecurityRequirement -> FilePath
$cshowList :: [SecurityRequirement] -> ShowS
showList :: [SecurityRequirement] -> ShowS
Show, NonEmpty SecurityRequirement -> SecurityRequirement
SecurityRequirement -> SecurityRequirement -> SecurityRequirement
(SecurityRequirement -> SecurityRequirement -> SecurityRequirement)
-> (NonEmpty SecurityRequirement -> SecurityRequirement)
-> (forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement)
-> Semigroup SecurityRequirement
forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
<> :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
$csconcat :: NonEmpty SecurityRequirement -> SecurityRequirement
sconcat :: NonEmpty SecurityRequirement -> SecurityRequirement
$cstimes :: forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement
stimes :: forall b.
Integral b =>
b -> SecurityRequirement -> SecurityRequirement
Semigroup, Semigroup SecurityRequirement
SecurityRequirement
Semigroup SecurityRequirement =>
SecurityRequirement
-> (SecurityRequirement
-> SecurityRequirement -> SecurityRequirement)
-> ([SecurityRequirement] -> SecurityRequirement)
-> Monoid SecurityRequirement
[SecurityRequirement] -> SecurityRequirement
SecurityRequirement -> SecurityRequirement -> SecurityRequirement
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: SecurityRequirement
mempty :: SecurityRequirement
$cmappend :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
mappend :: SecurityRequirement -> SecurityRequirement -> SecurityRequirement
$cmconcat :: [SecurityRequirement] -> SecurityRequirement
mconcat :: [SecurityRequirement] -> SecurityRequirement
Monoid, [SecurityRequirement] -> Value
[SecurityRequirement] -> Encoding
SecurityRequirement -> Value
SecurityRequirement -> Encoding
(SecurityRequirement -> Value)
-> (SecurityRequirement -> Encoding)
-> ([SecurityRequirement] -> Value)
-> ([SecurityRequirement] -> Encoding)
-> ToJSON SecurityRequirement
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: SecurityRequirement -> Value
toJSON :: SecurityRequirement -> Value
$ctoEncoding :: SecurityRequirement -> Encoding
toEncoding :: SecurityRequirement -> Encoding
$ctoJSONList :: [SecurityRequirement] -> Value
toJSONList :: [SecurityRequirement] -> Value
$ctoEncodingList :: [SecurityRequirement] -> Encoding
toEncodingList :: [SecurityRequirement] -> Encoding
ToJSON, Value -> Parser [SecurityRequirement]
Value -> Parser SecurityRequirement
(Value -> Parser SecurityRequirement)
-> (Value -> Parser [SecurityRequirement])
-> FromJSON SecurityRequirement
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser SecurityRequirement
parseJSON :: Value -> Parser SecurityRequirement
$cparseJSONList :: Value -> Parser [SecurityRequirement]
parseJSONList :: Value -> Parser [SecurityRequirement]
FromJSON, Typeable SecurityRequirement
Typeable SecurityRequirement =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement)
-> (SecurityRequirement -> Constr)
-> (SecurityRequirement -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement))
-> ((forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement)
-> Data SecurityRequirement
SecurityRequirement -> Constr
SecurityRequirement -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SecurityRequirement
-> c SecurityRequirement
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SecurityRequirement
$ctoConstr :: SecurityRequirement -> Constr
toConstr :: SecurityRequirement -> Constr
$cdataTypeOf :: SecurityRequirement -> DataType
dataTypeOf :: SecurityRequirement -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SecurityRequirement)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SecurityRequirement)
$cgmapT :: (forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement
gmapT :: (forall b. Data b => b -> b)
-> SecurityRequirement -> SecurityRequirement
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SecurityRequirement -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SecurityRequirement -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SecurityRequirement -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SecurityRequirement -> m SecurityRequirement
Data, Typeable)
type TagName = Text
data Tag = Tag
{
Tag -> Text
_tagName :: TagName
, Tag -> Maybe Text
_tagDescription :: Maybe Text
, Tag -> Maybe ExternalDocs
_tagExternalDocs :: Maybe ExternalDocs
} deriving (Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
/= :: Tag -> Tag -> Bool
Eq, Eq Tag
Eq Tag =>
(Tag -> Tag -> Ordering)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Tag)
-> (Tag -> Tag -> Tag)
-> Ord Tag
Tag -> Tag -> Bool
Tag -> Tag -> Ordering
Tag -> Tag -> Tag
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Tag -> Tag -> Ordering
compare :: Tag -> Tag -> Ordering
$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
>= :: Tag -> Tag -> Bool
$cmax :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
min :: Tag -> Tag -> Tag
Ord, Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> FilePath
(Int -> Tag -> ShowS)
-> (Tag -> FilePath) -> ([Tag] -> ShowS) -> Show Tag
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Tag -> ShowS
showsPrec :: Int -> Tag -> ShowS
$cshow :: Tag -> FilePath
show :: Tag -> FilePath
$cshowList :: [Tag] -> ShowS
showList :: [Tag] -> ShowS
Show, (forall x. Tag -> Rep Tag x)
-> (forall x. Rep Tag x -> Tag) -> Generic Tag
forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Tag -> Rep Tag x
from :: forall x. Tag -> Rep Tag x
$cto :: forall x. Rep Tag x -> Tag
to :: forall x. Rep Tag x -> Tag
Generic, Typeable Tag
Typeable Tag =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag)
-> (Tag -> Constr)
-> (Tag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag))
-> ((forall b. Data b => b -> b) -> Tag -> Tag)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall u. (forall d. Data d => d -> u) -> Tag -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag)
-> Data Tag
Tag -> Constr
Tag -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
$ctoConstr :: Tag -> Constr
toConstr :: Tag -> Constr
$cdataTypeOf :: Tag -> DataType
dataTypeOf :: Tag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
$cgmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
Data, Typeable)
instance Hashable Tag
instance IsString Tag where
fromString :: FilePath -> Tag
fromString FilePath
s = Text -> Maybe Text -> Maybe ExternalDocs -> Tag
Tag (FilePath -> Text
forall a. IsString a => FilePath -> a
fromString FilePath
s) Maybe Text
forall a. Maybe a
Nothing Maybe ExternalDocs
forall a. Maybe a
Nothing
data ExternalDocs = ExternalDocs
{
ExternalDocs -> Maybe Text
_externalDocsDescription :: Maybe Text
, ExternalDocs -> URL
_externalDocsUrl :: URL
} deriving (ExternalDocs -> ExternalDocs -> Bool
(ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool) -> Eq ExternalDocs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExternalDocs -> ExternalDocs -> Bool
== :: ExternalDocs -> ExternalDocs -> Bool
$c/= :: ExternalDocs -> ExternalDocs -> Bool
/= :: ExternalDocs -> ExternalDocs -> Bool
Eq, Eq ExternalDocs
Eq ExternalDocs =>
(ExternalDocs -> ExternalDocs -> Ordering)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> Bool)
-> (ExternalDocs -> ExternalDocs -> ExternalDocs)
-> (ExternalDocs -> ExternalDocs -> ExternalDocs)
-> Ord ExternalDocs
ExternalDocs -> ExternalDocs -> Bool
ExternalDocs -> ExternalDocs -> Ordering
ExternalDocs -> ExternalDocs -> ExternalDocs
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ExternalDocs -> ExternalDocs -> Ordering
compare :: ExternalDocs -> ExternalDocs -> Ordering
$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
>= :: ExternalDocs -> ExternalDocs -> Bool
$cmax :: ExternalDocs -> ExternalDocs -> ExternalDocs
max :: ExternalDocs -> ExternalDocs -> ExternalDocs
$cmin :: ExternalDocs -> ExternalDocs -> ExternalDocs
min :: ExternalDocs -> ExternalDocs -> ExternalDocs
Ord, Int -> ExternalDocs -> ShowS
[ExternalDocs] -> ShowS
ExternalDocs -> FilePath
(Int -> ExternalDocs -> ShowS)
-> (ExternalDocs -> FilePath)
-> ([ExternalDocs] -> ShowS)
-> Show ExternalDocs
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExternalDocs -> ShowS
showsPrec :: Int -> ExternalDocs -> ShowS
$cshow :: ExternalDocs -> FilePath
show :: ExternalDocs -> FilePath
$cshowList :: [ExternalDocs] -> ShowS
showList :: [ExternalDocs] -> ShowS
Show, (forall x. ExternalDocs -> Rep ExternalDocs x)
-> (forall x. Rep ExternalDocs x -> ExternalDocs)
-> Generic ExternalDocs
forall x. Rep ExternalDocs x -> ExternalDocs
forall x. ExternalDocs -> Rep ExternalDocs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExternalDocs -> Rep ExternalDocs x
from :: forall x. ExternalDocs -> Rep ExternalDocs x
$cto :: forall x. Rep ExternalDocs x -> ExternalDocs
to :: forall x. Rep ExternalDocs x -> ExternalDocs
Generic, Typeable ExternalDocs
Typeable ExternalDocs =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs)
-> (ExternalDocs -> Constr)
-> (ExternalDocs -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalDocs))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs))
-> ((forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r)
-> (forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs)
-> Data ExternalDocs
ExternalDocs -> Constr
ExternalDocs -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExternalDocs -> c ExternalDocs
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExternalDocs
$ctoConstr :: ExternalDocs -> Constr
toConstr :: ExternalDocs -> Constr
$cdataTypeOf :: ExternalDocs -> DataType
dataTypeOf :: ExternalDocs -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalDocs)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExternalDocs)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExternalDocs)
$cgmapT :: (forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs
gmapT :: (forall b. Data b => b -> b) -> ExternalDocs -> ExternalDocs
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExternalDocs -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExternalDocs -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExternalDocs -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExternalDocs -> m ExternalDocs
Data, Typeable)
instance Hashable ExternalDocs
newtype Reference = Reference { Reference -> Text
getReference :: Text }
deriving (Reference -> Reference -> Bool
(Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool) -> Eq Reference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Reference -> Reference -> Bool
== :: Reference -> Reference -> Bool
$c/= :: Reference -> Reference -> Bool
/= :: Reference -> Reference -> Bool
Eq, Int -> Reference -> ShowS
[Reference] -> ShowS
Reference -> FilePath
(Int -> Reference -> ShowS)
-> (Reference -> FilePath)
-> ([Reference] -> ShowS)
-> Show Reference
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Reference -> ShowS
showsPrec :: Int -> Reference -> ShowS
$cshow :: Reference -> FilePath
show :: Reference -> FilePath
$cshowList :: [Reference] -> ShowS
showList :: [Reference] -> ShowS
Show, Typeable Reference
Typeable Reference =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference)
-> (Reference -> Constr)
-> (Reference -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reference))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference))
-> ((forall b. Data b => b -> b) -> Reference -> Reference)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r)
-> (forall u. (forall d. Data d => d -> u) -> Reference -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Reference -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference)
-> Data Reference
Reference -> Constr
Reference -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reference -> c Reference
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reference
$ctoConstr :: Reference -> Constr
toConstr :: Reference -> Constr
$cdataTypeOf :: Reference -> DataType
dataTypeOf :: Reference -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reference)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reference)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference)
$cgmapT :: (forall b. Data b => b -> b) -> Reference -> Reference
gmapT :: (forall b. Data b => b -> b) -> Reference -> Reference
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reference -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Reference -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Reference -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reference -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reference -> m Reference
Data, Typeable)
data Referenced a
= Ref Reference
| Inline a
deriving (Referenced a -> Referenced a -> Bool
(Referenced a -> Referenced a -> Bool)
-> (Referenced a -> Referenced a -> Bool) -> Eq (Referenced a)
forall a. Eq a => Referenced a -> Referenced a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$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
/= :: Referenced a -> Referenced a -> Bool
Eq, Int -> Referenced a -> ShowS
[Referenced a] -> ShowS
Referenced a -> FilePath
(Int -> Referenced a -> ShowS)
-> (Referenced a -> FilePath)
-> ([Referenced a] -> ShowS)
-> Show (Referenced a)
forall a. Show a => Int -> Referenced a -> ShowS
forall a. Show a => [Referenced a] -> ShowS
forall a. Show a => Referenced a -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Referenced a -> ShowS
showsPrec :: Int -> Referenced a -> ShowS
$cshow :: forall a. Show a => Referenced a -> FilePath
show :: Referenced a -> FilePath
$cshowList :: forall a. Show a => [Referenced a] -> ShowS
showList :: [Referenced a] -> ShowS
Show, (forall a b. (a -> b) -> Referenced a -> Referenced b)
-> (forall a b. a -> Referenced b -> Referenced a)
-> Functor Referenced
forall a b. a -> Referenced b -> Referenced a
forall a b. (a -> b) -> Referenced a -> Referenced b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Referenced a -> Referenced b
fmap :: forall a b. (a -> b) -> Referenced a -> Referenced b
$c<$ :: forall a b. a -> Referenced b -> Referenced a
<$ :: forall a b. a -> Referenced b -> Referenced a
Functor, Typeable (Referenced a)
Typeable (Referenced a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a))
-> (Referenced a -> Constr)
-> (Referenced a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a)))
-> ((forall b. Data b => b -> b) -> Referenced a -> Referenced a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Referenced a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Referenced a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a))
-> Data (Referenced a)
Referenced a -> Constr
Referenced a -> DataType
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
forall a. Data a => Typeable (Referenced a)
forall a. Data a => Referenced a -> Constr
forall a. Data a => Referenced a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Referenced a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Referenced a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Referenced a -> u
forall u. (forall d. Data d => d -> u) -> Referenced a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> c (Referenced a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
$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)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Referenced a -> 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)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Referenced a)
$ctoConstr :: forall a. Data a => Referenced a -> Constr
toConstr :: Referenced a -> Constr
$cdataTypeOf :: forall a. Data a => Referenced a -> DataType
dataTypeOf :: Referenced a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Referenced a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> 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))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Referenced a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Referenced a -> Referenced a
gmapT :: (forall b. Data b => b -> b) -> Referenced a -> Referenced a
$cgmapQl :: 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
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Referenced a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Referenced a -> [u]
gmapQ :: forall u. (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
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Referenced a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad 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)
$cgmapMp :: 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)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Referenced a -> m (Referenced a)
Data, Typeable)
instance IsString a => IsString (Referenced a) where
fromString :: FilePath -> Referenced a
fromString = a -> Referenced a
forall a. a -> Referenced a
Inline (a -> Referenced a) -> (FilePath -> a) -> FilePath -> Referenced a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> a
forall a. IsString a => FilePath -> a
fromString
newtype URL = URL { URL -> Text
getUrl :: Text } deriving (URL -> URL -> Bool
(URL -> URL -> Bool) -> (URL -> URL -> Bool) -> Eq URL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: URL -> URL -> Bool
== :: URL -> URL -> Bool
$c/= :: URL -> URL -> Bool
/= :: URL -> URL -> Bool
Eq, Eq URL
Eq URL =>
(URL -> URL -> Ordering)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> Bool)
-> (URL -> URL -> URL)
-> (URL -> URL -> URL)
-> Ord URL
URL -> URL -> Bool
URL -> URL -> Ordering
URL -> URL -> URL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: URL -> URL -> Ordering
compare :: URL -> URL -> Ordering
$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
>= :: URL -> URL -> Bool
$cmax :: URL -> URL -> URL
max :: URL -> URL -> URL
$cmin :: URL -> URL -> URL
min :: URL -> URL -> URL
Ord, Int -> URL -> ShowS
[URL] -> ShowS
URL -> FilePath
(Int -> URL -> ShowS)
-> (URL -> FilePath) -> ([URL] -> ShowS) -> Show URL
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> URL -> ShowS
showsPrec :: Int -> URL -> ShowS
$cshow :: URL -> FilePath
show :: URL -> FilePath
$cshowList :: [URL] -> ShowS
showList :: [URL] -> ShowS
Show, Eq URL
Eq URL => (Int -> URL -> Int) -> (URL -> Int) -> Hashable URL
Int -> URL -> Int
URL -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> URL -> Int
hashWithSalt :: Int -> URL -> Int
$chash :: URL -> Int
hash :: URL -> Int
Hashable, [URL] -> Value
[URL] -> Encoding
URL -> Value
URL -> Encoding
(URL -> Value)
-> (URL -> Encoding)
-> ([URL] -> Value)
-> ([URL] -> Encoding)
-> ToJSON URL
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: URL -> Value
toJSON :: URL -> Value
$ctoEncoding :: URL -> Encoding
toEncoding :: URL -> Encoding
$ctoJSONList :: [URL] -> Value
toJSONList :: [URL] -> Value
$ctoEncodingList :: [URL] -> Encoding
toEncodingList :: [URL] -> Encoding
ToJSON, Value -> Parser [URL]
Value -> Parser URL
(Value -> Parser URL) -> (Value -> Parser [URL]) -> FromJSON URL
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser URL
parseJSON :: Value -> Parser URL
$cparseJSONList :: Value -> Parser [URL]
parseJSONList :: Value -> Parser [URL]
FromJSON, Typeable URL
Typeable URL =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL)
-> (URL -> Constr)
-> (URL -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c URL))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL))
-> ((forall b. Data b => b -> b) -> URL -> URL)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r)
-> (forall u. (forall d. Data d => d -> u) -> URL -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> URL -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> URL -> m URL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL)
-> Data URL
URL -> Constr
URL -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> URL -> c URL
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c URL
$ctoConstr :: URL -> Constr
toConstr :: URL -> Constr
$cdataTypeOf :: URL -> DataType
dataTypeOf :: URL -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c URL)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c URL)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URL)
$cgmapT :: (forall b. Data b => b -> b) -> URL -> URL
gmapT :: (forall b. Data b => b -> b) -> URL -> URL
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URL -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> URL -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> URL -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> URL -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> URL -> m URL
Data, Typeable)
data AdditionalProperties
= AdditionalPropertiesAllowed Bool
| AdditionalPropertiesSchema (Referenced Schema)
deriving (AdditionalProperties -> AdditionalProperties -> Bool
(AdditionalProperties -> AdditionalProperties -> Bool)
-> (AdditionalProperties -> AdditionalProperties -> Bool)
-> Eq AdditionalProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdditionalProperties -> AdditionalProperties -> Bool
== :: AdditionalProperties -> AdditionalProperties -> Bool
$c/= :: AdditionalProperties -> AdditionalProperties -> Bool
/= :: AdditionalProperties -> AdditionalProperties -> Bool
Eq, Int -> AdditionalProperties -> ShowS
[AdditionalProperties] -> ShowS
AdditionalProperties -> FilePath
(Int -> AdditionalProperties -> ShowS)
-> (AdditionalProperties -> FilePath)
-> ([AdditionalProperties] -> ShowS)
-> Show AdditionalProperties
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdditionalProperties -> ShowS
showsPrec :: Int -> AdditionalProperties -> ShowS
$cshow :: AdditionalProperties -> FilePath
show :: AdditionalProperties -> FilePath
$cshowList :: [AdditionalProperties] -> ShowS
showList :: [AdditionalProperties] -> ShowS
Show, Typeable AdditionalProperties
Typeable AdditionalProperties =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties)
-> (AdditionalProperties -> Constr)
-> (AdditionalProperties -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties))
-> ((forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r)
-> (forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties)
-> Data AdditionalProperties
AdditionalProperties -> Constr
AdditionalProperties -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> AdditionalProperties
-> c AdditionalProperties
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AdditionalProperties
$ctoConstr :: AdditionalProperties -> Constr
toConstr :: AdditionalProperties -> Constr
$cdataTypeOf :: AdditionalProperties -> DataType
dataTypeOf :: AdditionalProperties -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AdditionalProperties)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AdditionalProperties)
$cgmapT :: (forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties
gmapT :: (forall b. Data b => b -> b)
-> AdditionalProperties -> AdditionalProperties
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AdditionalProperties -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> AdditionalProperties -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AdditionalProperties -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AdditionalProperties -> m AdditionalProperties
Data, Typeable)
newtype OpenApiSpecVersion = OpenApiSpecVersion {OpenApiSpecVersion -> Version
getVersion :: Version} deriving (OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
(OpenApiSpecVersion -> OpenApiSpecVersion -> Bool)
-> (OpenApiSpecVersion -> OpenApiSpecVersion -> Bool)
-> Eq OpenApiSpecVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
== :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
$c/= :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
/= :: OpenApiSpecVersion -> OpenApiSpecVersion -> Bool
Eq, Int -> OpenApiSpecVersion -> ShowS
[OpenApiSpecVersion] -> ShowS
OpenApiSpecVersion -> FilePath
(Int -> OpenApiSpecVersion -> ShowS)
-> (OpenApiSpecVersion -> FilePath)
-> ([OpenApiSpecVersion] -> ShowS)
-> Show OpenApiSpecVersion
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenApiSpecVersion -> ShowS
showsPrec :: Int -> OpenApiSpecVersion -> ShowS
$cshow :: OpenApiSpecVersion -> FilePath
show :: OpenApiSpecVersion -> FilePath
$cshowList :: [OpenApiSpecVersion] -> ShowS
showList :: [OpenApiSpecVersion] -> ShowS
Show, (forall x. OpenApiSpecVersion -> Rep OpenApiSpecVersion x)
-> (forall x. Rep OpenApiSpecVersion x -> OpenApiSpecVersion)
-> Generic OpenApiSpecVersion
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
$cfrom :: forall x. OpenApiSpecVersion -> Rep OpenApiSpecVersion x
from :: forall x. OpenApiSpecVersion -> Rep OpenApiSpecVersion x
$cto :: forall x. Rep OpenApiSpecVersion x -> OpenApiSpecVersion
to :: forall x. Rep OpenApiSpecVersion x -> OpenApiSpecVersion
Generic, Typeable OpenApiSpecVersion
Typeable OpenApiSpecVersion =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion)
-> (OpenApiSpecVersion -> Constr)
-> (OpenApiSpecVersion -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion)
-> (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 u.
(forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiSpecVersion -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion)
-> Data OpenApiSpecVersion
OpenApiSpecVersion -> Constr
OpenApiSpecVersion -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OpenApiSpecVersion
-> c OpenApiSpecVersion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OpenApiSpecVersion
$ctoConstr :: OpenApiSpecVersion -> Constr
toConstr :: OpenApiSpecVersion -> Constr
$cdataTypeOf :: OpenApiSpecVersion -> DataType
dataTypeOf :: OpenApiSpecVersion -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiSpecVersion)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OpenApiSpecVersion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiSpecVersion)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OpenApiSpecVersion)
$cgmapT :: (forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion
gmapT :: (forall b. Data b => b -> b)
-> OpenApiSpecVersion -> OpenApiSpecVersion
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OpenApiSpecVersion -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OpenApiSpecVersion -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiSpecVersion -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OpenApiSpecVersion -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m OpenApiSpecVersion
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OpenApiSpecVersion -> m 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 (Version -> OpenApiSpecVersion) -> Version -> OpenApiSpecVersion
forall a b. (a -> b) -> a -> b
$ Version -> Version -> Version
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 = OpenApiSpecVersion -> OpenApiSpecVersion -> OpenApiSpecVersion
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup OpenApi where
<> :: OpenApi -> OpenApi -> OpenApi
(<>) = OpenApi -> OpenApi -> OpenApi
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid OpenApi where
mempty :: OpenApi
mempty = OpenApi
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: OpenApi -> OpenApi -> OpenApi
mappend = OpenApi -> OpenApi -> OpenApi
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Info where
<> :: Info -> Info -> Info
(<>) = Info -> Info -> Info
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Info where
mempty :: Info
mempty = Info
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Info -> Info -> Info
mappend = Info -> Info -> Info
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Contact where
<> :: Contact -> Contact -> Contact
(<>) = Contact -> Contact -> Contact
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Contact where
mempty :: Contact
mempty = Contact
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Contact -> Contact -> Contact
mappend = Contact -> Contact -> Contact
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Components where
<> :: Components -> Components -> Components
(<>) = Components -> Components -> Components
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Components where
mempty :: Components
mempty = Components
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Components -> Components -> Components
mappend = Components -> Components -> Components
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup PathItem where
<> :: PathItem -> PathItem -> PathItem
(<>) = PathItem -> PathItem -> PathItem
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid PathItem where
mempty :: PathItem
mempty = PathItem
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: PathItem -> PathItem -> PathItem
mappend = PathItem -> PathItem -> PathItem
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Schema where
<> :: Schema -> Schema -> Schema
(<>) = Schema -> Schema -> Schema
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Schema where
mempty :: Schema
mempty = Schema
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Schema -> Schema -> Schema
mappend = Schema -> Schema -> Schema
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Param where
<> :: Param -> Param -> Param
(<>) = Param -> Param -> Param
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Param where
mempty :: Param
mempty = Param
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Param -> Param -> Param
mappend = Param -> Param -> Param
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Header where
<> :: Header -> Header -> Header
(<>) = Header -> Header -> Header
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Header where
mempty :: Header
mempty = Header
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Header -> Header -> Header
mappend = Header -> Header -> Header
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Responses where
<> :: Responses -> Responses -> Responses
(<>) = Responses -> Responses -> Responses
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Responses where
mempty :: Responses
mempty = Responses
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Responses -> Responses -> Responses
mappend = Responses -> Responses -> Responses
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Response where
<> :: Response -> Response -> Response
(<>) = Response -> Response -> Response
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Response where
mempty :: Response
mempty = Response
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Response -> Response -> Response
mappend = Response -> Response -> Response
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup MediaTypeObject where
<> :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
(<>) = MediaTypeObject -> MediaTypeObject -> MediaTypeObject
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid MediaTypeObject where
mempty :: MediaTypeObject
mempty = MediaTypeObject
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: MediaTypeObject -> MediaTypeObject -> MediaTypeObject
mappend = MediaTypeObject -> MediaTypeObject -> MediaTypeObject
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Encoding where
<> :: Encoding -> Encoding -> Encoding
(<>) = Encoding -> Encoding -> Encoding
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Encoding where
mempty :: Encoding
mempty = Encoding
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Encoding -> Encoding -> Encoding
mappend = Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup ExternalDocs where
<> :: ExternalDocs -> ExternalDocs -> ExternalDocs
(<>) = ExternalDocs -> ExternalDocs -> ExternalDocs
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid ExternalDocs where
mempty :: ExternalDocs
mempty = ExternalDocs
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: ExternalDocs -> ExternalDocs -> ExternalDocs
mappend = ExternalDocs -> ExternalDocs -> ExternalDocs
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Operation where
<> :: Operation -> Operation -> Operation
(<>) = Operation -> Operation -> Operation
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid Operation where
mempty :: Operation
mempty = Operation
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: Operation -> Operation -> Operation
mappend = Operation -> Operation -> Operation
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup (OAuth2Flow p) where
l :: OAuth2Flow p
l@OAuth2Flow{ _oAath2RefreshUrl :: forall p. OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl = Maybe URL
lUrl, _oAuth2Scopes :: forall p. OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes = InsOrdHashMap Text Text
lScopes }
<> :: OAuth2Flow p -> OAuth2Flow p -> OAuth2Flow p
<> OAuth2Flow { _oAath2RefreshUrl :: forall p. OAuth2Flow p -> Maybe URL
_oAath2RefreshUrl = Maybe URL
rUrl, _oAuth2Scopes :: forall p. OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes = InsOrdHashMap Text Text
rScopes } =
OAuth2Flow p
l { _oAath2RefreshUrl = swaggerMappend lUrl rUrl, _oAuth2Scopes = lScopes <> 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 Maybe (OAuth2Flow OAuth2ImplicitFlow)
-> Maybe (OAuth2Flow OAuth2ImplicitFlow)
-> Maybe (OAuth2Flow OAuth2ImplicitFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2ImplicitFlow)
_oAuth2FlowsImplicit OAuth2Flows
r
, _oAuth2FlowsPassword :: Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword = OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword OAuth2Flows
l Maybe (OAuth2Flow OAuth2PasswordFlow)
-> Maybe (OAuth2Flow OAuth2PasswordFlow)
-> Maybe (OAuth2Flow OAuth2PasswordFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2PasswordFlow)
_oAuth2FlowsPassword OAuth2Flows
r
, _oAuth2FlowsClientCredentials :: Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials = OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials OAuth2Flows
l Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
-> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
-> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2ClientCredentialsFlow)
_oAuth2FlowsClientCredentials OAuth2Flows
r
, _oAuth2FlowsAuthorizationCode :: Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode = OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode OAuth2Flows
l Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
-> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
-> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows -> Maybe (OAuth2Flow OAuth2AuthorizationCodeFlow)
_oAuth2FlowsAuthorizationCode OAuth2Flows
r
}
instance Monoid OAuth2Flows where
mempty :: OAuth2Flows
mempty = OAuth2Flows
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: OAuth2Flows -> OAuth2Flows -> OAuth2Flows
mappend = OAuth2Flows -> OAuth2Flows -> OAuth2Flows
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup SecurityScheme where
SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
lFlows) Maybe Text
lDesc
<> :: SecurityScheme -> SecurityScheme -> SecurityScheme
<> SecurityScheme (SecuritySchemeOAuth2 OAuth2Flows
rFlows) Maybe Text
rDesc =
SecuritySchemeType -> Maybe Text -> SecurityScheme
SecurityScheme (OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Flows -> SecuritySchemeType)
-> OAuth2Flows -> SecuritySchemeType
forall a b. (a -> b) -> a -> b
$ OAuth2Flows
lFlows OAuth2Flows -> OAuth2Flows -> OAuth2Flows
forall a. Semigroup a => a -> a -> a
<> OAuth2Flows
rFlows) (Maybe Text -> Maybe Text -> Maybe Text
forall m. SwaggerMonoid m => m -> m -> m
swaggerMappend Maybe Text
lDesc Maybe Text
rDesc)
SecurityScheme
l <> SecurityScheme
_ = SecurityScheme
l
instance Semigroup SecurityDefinitions where
(SecurityDefinitions Definitions SecurityScheme
sd1) <> :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
<> (SecurityDefinitions Definitions SecurityScheme
sd2) =
Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions (Definitions SecurityScheme -> SecurityDefinitions)
-> Definitions SecurityScheme -> SecurityDefinitions
forall a b. (a -> b) -> a -> b
$ (SecurityScheme -> SecurityScheme -> SecurityScheme)
-> Definitions SecurityScheme
-> Definitions SecurityScheme
-> Definitions SecurityScheme
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith SecurityScheme -> SecurityScheme -> SecurityScheme
forall a. Semigroup a => a -> a -> a
(<>) Definitions SecurityScheme
sd1 Definitions SecurityScheme
sd2
instance Monoid SecurityDefinitions where
mempty :: SecurityDefinitions
mempty = Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions Definitions SecurityScheme
forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
mappend :: SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
mappend = SecurityDefinitions -> SecurityDefinitions -> SecurityDefinitions
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup RequestBody where
<> :: RequestBody -> RequestBody -> RequestBody
(<>) = RequestBody -> RequestBody -> RequestBody
forall a. (Generic a, GMonoid (Rep a)) => a -> a -> a
genericMappend
instance Monoid RequestBody where
mempty :: RequestBody
mempty = RequestBody
forall a. (Generic a, GMonoid (Rep a)) => a
genericMempty
mappend :: RequestBody -> RequestBody -> RequestBody
mappend = RequestBody -> RequestBody -> RequestBody
forall a. Semigroup a => a -> a -> a
(<>)
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 = InsOrdHashMap FilePath PathItem
forall k v. InsOrdHashMap k v
InsOrdHashMap.empty
swaggerMappend :: InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
swaggerMappend = (PathItem -> PathItem -> PathItem)
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v)
-> InsOrdHashMap k v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.unionWith PathItem -> PathItem -> PathItem
forall a. Monoid a => a -> a -> a
mappend
instance Monoid a => SwaggerMonoid (Referenced a) where
swaggerMempty :: Referenced a
swaggerMempty = a -> Referenced a
forall a. a -> Referenced a
Inline a
forall a. Monoid a => a
mempty
swaggerMappend :: Referenced a -> Referenced a -> Referenced a
swaggerMappend (Inline a
x) (Inline a
y) = a -> Referenced a
forall a. a -> Referenced a
Inline (a -> a -> a
forall a. Monoid a => a -> a -> a
mappend a
x a
y)
swaggerMappend Referenced a
_ Referenced a
y = Referenced a
y
instance ToJSON Style where
toJSON :: Style -> Value
toJSON = Options -> Style -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Style")
instance ToJSON OpenApiType where
toJSON :: OpenApiType -> Value
toJSON = Options -> OpenApiType -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Swagger")
instance ToJSON ParamLocation where
toJSON :: ParamLocation -> Value
toJSON = Options -> ParamLocation -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Param")
instance ToJSON Info where
toJSON :: Info -> Value
toJSON = Options -> Info -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Info")
instance ToJSON Contact where
toJSON :: Contact -> Value
toJSON = Options -> Contact -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Contact")
instance ToJSON License where
toJSON :: License -> Value
toJSON = Options -> License -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"License")
instance ToJSON ServerVariable where
toJSON :: ServerVariable -> Value
toJSON = Options -> ServerVariable -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"ServerVariable")
instance ToJSON ApiKeyLocation where
toJSON :: ApiKeyLocation -> Value
toJSON = Options -> ApiKeyLocation -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"ApiKey")
instance ToJSON ApiKeyParams where
toJSON :: ApiKeyParams -> Value
toJSON = Options -> ApiKeyParams -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"apiKey")
instance ToJSON Tag where
toJSON :: Tag -> Value
toJSON = Options -> Tag -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Tag")
instance ToJSON ExternalDocs where
toJSON :: ExternalDocs -> Value
toJSON = Options -> ExternalDocs -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"ExternalDocs")
instance ToJSON Xml where
toJSON :: Xml -> Value
toJSON = Options -> Xml -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Xml")
instance ToJSON Discriminator where
toJSON :: Discriminator -> Value
toJSON = Options -> Discriminator -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"Discriminator")
instance ToJSON OAuth2ImplicitFlow where
toJSON :: OAuth2ImplicitFlow -> Value
toJSON = Options -> OAuth2ImplicitFlow -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2ImplicitFlow")
instance ToJSON OAuth2PasswordFlow where
toJSON :: OAuth2PasswordFlow -> Value
toJSON = Options -> OAuth2PasswordFlow -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2PasswordFlow")
instance ToJSON OAuth2ClientCredentialsFlow where
toJSON :: OAuth2ClientCredentialsFlow -> Value
toJSON = Options -> OAuth2ClientCredentialsFlow -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2ClientCredentialsFlow")
instance ToJSON OAuth2AuthorizationCodeFlow where
toJSON :: OAuth2AuthorizationCodeFlow -> Value
toJSON = Options -> OAuth2AuthorizationCodeFlow -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2AuthorizationCodeFlow")
instance FromJSON Style where
parseJSON :: Value -> Parser Style
parseJSON = Options -> Value -> Parser Style
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Style")
instance FromJSON OpenApiType where
parseJSON :: Value -> Parser OpenApiType
parseJSON = Options -> Value -> Parser OpenApiType
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Swagger")
instance FromJSON ParamLocation where
parseJSON :: Value -> Parser ParamLocation
parseJSON = Options -> Value -> Parser ParamLocation
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Param")
instance FromJSON Info where
parseJSON :: Value -> Parser Info
parseJSON = Options -> Value -> Parser Info
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Info")
instance FromJSON Contact where
parseJSON :: Value -> Parser Contact
parseJSON = Options -> Value -> Parser Contact
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Contact")
instance FromJSON License where
parseJSON :: Value -> Parser License
parseJSON = Options -> Value -> Parser License
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"License")
instance FromJSON ServerVariable where
parseJSON :: Value -> Parser ServerVariable
parseJSON = Options -> Value -> Parser ServerVariable
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"ServerVariable")
instance FromJSON ApiKeyLocation where
parseJSON :: Value -> Parser ApiKeyLocation
parseJSON = Options -> Value -> Parser ApiKeyLocation
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"ApiKey")
instance FromJSON ApiKeyParams where
parseJSON :: Value -> Parser ApiKeyParams
parseJSON = Options -> Value -> Parser ApiKeyParams
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"apiKey")
instance FromJSON Tag where
parseJSON :: Value -> Parser Tag
parseJSON = Options -> Value -> Parser Tag
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Tag")
instance FromJSON ExternalDocs where
parseJSON :: Value -> Parser ExternalDocs
parseJSON = Options -> Value -> Parser ExternalDocs
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"ExternalDocs")
instance FromJSON Discriminator where
parseJSON :: Value -> Parser Discriminator
parseJSON = Options -> Value -> Parser Discriminator
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"Discriminator")
instance FromJSON OAuth2ImplicitFlow where
parseJSON :: Value -> Parser OAuth2ImplicitFlow
parseJSON = Options -> Value -> Parser OAuth2ImplicitFlow
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2ImplicitFlow")
instance FromJSON OAuth2PasswordFlow where
parseJSON :: Value -> Parser OAuth2PasswordFlow
parseJSON = Options -> Value -> Parser OAuth2PasswordFlow
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2PasswordFlow")
instance FromJSON OAuth2ClientCredentialsFlow where
parseJSON :: Value -> Parser OAuth2ClientCredentialsFlow
parseJSON = Options -> Value -> Parser OAuth2ClientCredentialsFlow
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2ClientCredentialsFlow")
instance FromJSON OAuth2AuthorizationCodeFlow where
parseJSON :: Value -> Parser OAuth2AuthorizationCodeFlow
parseJSON = Options -> Value -> Parser OAuth2AuthorizationCodeFlow
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"OAuth2AuthorizationCodeFlow")
instance ToJSON OpenApiSpecVersion where
toJSON :: OpenApiSpecVersion -> Value
toJSON (OpenApiSpecVersion Version
v)= FilePath -> Value
forall a. ToJSON a => a -> Value
toJSON (FilePath -> Value) -> (Version -> FilePath) -> Version -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> FilePath
showVersion (Version -> Value) -> Version -> Value
forall a b. (a -> b) -> a -> b
$ Version
v
instance ToJSON MediaType where
toJSON :: MediaType -> Value
toJSON = FilePath -> Value
forall a. ToJSON a => a -> Value
toJSON (FilePath -> Value)
-> (MediaType -> FilePath) -> MediaType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show
toEncoding :: MediaType -> Encoding
toEncoding = FilePath -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (FilePath -> Encoding)
-> (MediaType -> FilePath) -> MediaType -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show
instance ToJSONKey MediaType where
toJSONKey :: ToJSONKeyFunction MediaType
toJSONKey = (MediaType -> Text) -> ToJSONKeyFunction MediaType
forall a. (a -> Text) -> ToJSONKeyFunction a
JSON.toJSONKeyText (FilePath -> Text
Text.pack (FilePath -> Text) -> (MediaType -> FilePath) -> MediaType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> FilePath
forall a. Show a => a -> FilePath
show)
instance (Eq p, ToJSON p, AesonDefaultValue p) => ToJSON (OAuth2Flow p) where
toJSON :: OAuth2Flow p -> Value
toJSON OAuth2Flow p
a = OAuth2Flow p -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON OAuth2Flow p
a Value -> (Value -> Value) -> Value
forall a b. a -> (a -> b) -> b
&
if InsOrdHashMap Text Text -> Bool
forall k v. InsOrdHashMap k v -> Bool
InsOrdHashMap.null (OAuth2Flow p -> InsOrdHashMap Text Text
forall p. OAuth2Flow p -> InsOrdHashMap Text Text
_oAuth2Scopes OAuth2Flow p
a)
then (Value -> Value -> Value
<+> [Pair] -> Value
object [Key
"scopes" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Pair] -> Value
object []])
else Value -> Value
forall a. a -> a
id
toEncoding :: OAuth2Flow p -> Encoding
toEncoding = OAuth2Flow p -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON OAuth2Flows where
toJSON :: OAuth2Flows -> Value
toJSON = OAuth2Flows -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: OAuth2Flows -> Encoding
toEncoding = OAuth2Flows -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON SecuritySchemeType where
toJSON :: SecuritySchemeType -> Value
toJSON (SecuritySchemeHttp HttpSchemeType
ty) = case HttpSchemeType
ty of
HttpSchemeBearer Maybe Text
mFmt ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"http" :: Text)
, Key
"scheme" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"bearer" :: Text)
] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
t -> [Key
"bearerFormat" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Text
t]) Maybe Text
mFmt
HttpSchemeType
HttpSchemeBasic ->
[Pair] -> Value
object [ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"http" :: Text)
, Key
"scheme" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"basic" :: Text)
]
HttpSchemeCustom Text
t ->
[Pair] -> Value
object [ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"http" :: Text)
, Key
"scheme" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Text
t
]
toJSON (SecuritySchemeApiKey ApiKeyParams
params)
= ApiKeyParams -> Value
forall a. ToJSON a => a -> Value
toJSON ApiKeyParams
params
Value -> Value -> Value
<+> [Pair] -> Value
object [ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"apiKey" :: Text) ]
toJSON (SecuritySchemeOAuth2 OAuth2Flows
params) = [Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"oauth2" :: Text)
, Key
"flows" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= OAuth2Flows -> Value
forall a. ToJSON a => a -> Value
toJSON OAuth2Flows
params
]
toJSON (SecuritySchemeOpenIdConnect URL
url) = [Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
"openIdConnect" :: Text)
, Key
"openIdConnectUrl" Key -> URL -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= URL
url
]
instance ToJSON OpenApi where
toJSON :: OpenApi -> Value
toJSON OpenApi
a = OpenApi -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON OpenApi
a Value -> (Value -> Value) -> Value
forall a b. a -> (a -> b) -> b
&
if InsOrdHashMap FilePath PathItem -> Bool
forall k v. InsOrdHashMap k v -> Bool
InsOrdHashMap.null (OpenApi -> InsOrdHashMap FilePath PathItem
_openApiPaths OpenApi
a)
then (Value -> Value -> Value
<+> [Pair] -> Value
object [Key
"paths" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Pair] -> Value
object []])
else Value -> Value
forall a. a -> a
id
toEncoding :: OpenApi -> Encoding
toEncoding = OpenApi -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Server where
toJSON :: Server -> Value
toJSON = Server -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Server -> Encoding
toEncoding = Server -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON SecurityScheme where
toJSON :: SecurityScheme -> Value
toJSON = SecurityScheme -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: SecurityScheme -> Encoding
toEncoding = SecurityScheme -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Schema where
toJSON :: Schema -> Value
toJSON = SwaggerAesonOptions -> Schema -> Value
forall a (xs :: [*]).
(Generic a, All2 AesonDefaultValue (Code a), HasDatatypeInfo a,
All2 ToJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
SwaggerAesonOptions -> a -> Value
sopSwaggerGenericToJSONWithOpts (SwaggerAesonOptions -> Schema -> Value)
-> SwaggerAesonOptions -> Schema -> Value
forall a b. (a -> b) -> a -> b
$
FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"schema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"items"
instance ToJSON Header where
toJSON :: Header -> Value
toJSON = Header -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Header -> Encoding
toEncoding = Header -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON OpenApiItems where
toJSON :: OpenApiItems -> Value
toJSON (OpenApiItemsObject Referenced Schema
x) = [Pair] -> Value
object [ Key
"items" Key -> Referenced Schema -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Referenced Schema
x ]
toJSON (OpenApiItemsArray []) = [Pair] -> Value
object
[ Key
"items" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Pair] -> Value
object []
, Key
"maxItems" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Int
0 :: Int)
, Key
"example" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Array -> Value
Array Array
forall a. Monoid a => a
mempty
]
toJSON (OpenApiItemsArray [Referenced Schema]
x) = [Pair] -> Value
object [ Key
"items" Key -> [Referenced Schema] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Referenced Schema]
x ]
instance ToJSON Components where
toJSON :: Components -> Value
toJSON = Components -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Components -> Encoding
toEncoding = Components -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON MimeList where
toJSON :: MimeList -> Value
toJSON (MimeList [MediaType]
xs) = [FilePath] -> Value
forall a. ToJSON a => a -> Value
toJSON ((MediaType -> FilePath) -> [MediaType] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map MediaType -> FilePath
forall a. Show a => a -> FilePath
show [MediaType]
xs)
instance ToJSON Param where
toJSON :: Param -> Value
toJSON = Param -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Param -> Encoding
toEncoding = Param -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Responses where
toJSON :: Responses -> Value
toJSON = Responses -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Responses -> Encoding
toEncoding = Responses -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Response where
toJSON :: Response -> Value
toJSON = Response -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Response -> Encoding
toEncoding = Response -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Operation where
toJSON :: Operation -> Value
toJSON = Operation -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Operation -> Encoding
toEncoding = Operation -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON PathItem where
toJSON :: PathItem -> Value
toJSON = PathItem -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: PathItem -> Encoding
toEncoding = PathItem -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON RequestBody where
toJSON :: RequestBody -> Value
toJSON = RequestBody -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: RequestBody -> Encoding
toEncoding = RequestBody -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON MediaTypeObject where
toJSON :: MediaTypeObject -> Value
toJSON = MediaTypeObject -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: MediaTypeObject -> Encoding
toEncoding = MediaTypeObject -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Example where
toJSON :: Example -> Value
toJSON = Example -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Example -> Encoding
toEncoding = Example -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Encoding where
toJSON :: Encoding -> Value
toJSON = Encoding -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Encoding -> Encoding
toEncoding = Encoding -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON Link where
toJSON :: Link -> Value
toJSON = Link -> Value
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Value
sopSwaggerGenericToJSON
toEncoding :: Link -> Encoding
toEncoding = Link -> Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a, All2 ToJSON (Code a),
All2 Eq (Code a), Code a ~ '[xs]) =>
a -> Encoding
sopSwaggerGenericToEncoding
instance ToJSON SecurityDefinitions where
toJSON :: SecurityDefinitions -> Value
toJSON (SecurityDefinitions Definitions SecurityScheme
sd) = Definitions SecurityScheme -> Value
forall a. ToJSON a => a -> Value
toJSON Definitions SecurityScheme
sd
instance ToJSON Reference where
toJSON :: Reference -> Value
toJSON (Reference Text
ref) = [Pair] -> Value
object [ Key
"$ref" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Text
ref ]
referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
referencedToJSON :: forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
prefix (Ref (Reference Text
ref)) = [Pair] -> Value
object [ Key
"$ref" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref) ]
referencedToJSON Text
_ (Inline a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x
instance ToJSON (Referenced Schema) where toJSON :: Referenced Schema -> Value
toJSON = Text -> Referenced Schema -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/schemas/"
instance ToJSON (Referenced Param) where toJSON :: Referenced Param -> Value
toJSON = Text -> Referenced Param -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/parameters/"
instance ToJSON (Referenced Response) where toJSON :: Referenced Response -> Value
toJSON = Text -> Referenced Response -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/responses/"
instance ToJSON (Referenced RequestBody) where toJSON :: Referenced RequestBody -> Value
toJSON = Text -> Referenced RequestBody -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/requestBodies/"
instance ToJSON (Referenced Example) where toJSON :: Referenced Example -> Value
toJSON = Text -> Referenced Example -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/examples/"
instance ToJSON (Referenced Header) where toJSON :: Referenced Header -> Value
toJSON = Text -> Referenced Header -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/headers/"
instance ToJSON (Referenced Link) where toJSON :: Referenced Link -> Value
toJSON = Text -> Referenced Link -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/links/"
instance ToJSON (Referenced Callback) where toJSON :: Referenced Callback -> Value
toJSON = Text -> Referenced Callback -> Value
forall a. ToJSON a => Text -> Referenced a -> Value
referencedToJSON Text
"#/components/callbacks/"
instance ToJSON AdditionalProperties where
toJSON :: AdditionalProperties -> Value
toJSON (AdditionalPropertiesAllowed Bool
b) = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
b
toJSON (AdditionalPropertiesSchema Referenced Schema
s) = Referenced Schema -> Value
forall a. ToJSON a => a -> Value
toJSON Referenced Schema
s
instance ToJSON ExpressionOrValue where
toJSON :: ExpressionOrValue -> Value
toJSON (Expression Text
expr) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
expr
toJSON (Value Value
val) = Value -> Value
forall a. ToJSON a => a -> Value
toJSON Value
val
instance ToJSON Callback where
toJSON :: Callback -> Value
toJSON (Callback InsOrdHashMap Text PathItem
ps) = InsOrdHashMap Text PathItem -> Value
forall a. ToJSON a => a -> Value
toJSON InsOrdHashMap Text PathItem
ps
instance FromJSON OpenApiSpecVersion where
parseJSON :: Value -> Parser OpenApiSpecVersion
parseJSON = FilePath
-> (Text -> Parser OpenApiSpecVersion)
-> Value
-> Parser OpenApiSpecVersion
forall a. FilePath -> (Text -> Parser a) -> Value -> Parser a
withText FilePath
"OpenApiSpecVersion" ((Text -> Parser OpenApiSpecVersion)
-> Value -> Parser OpenApiSpecVersion)
-> (Text -> Parser OpenApiSpecVersion)
-> Value
-> Parser OpenApiSpecVersion
forall a b. (a -> b) -> a -> b
$ \Text
str ->
let validatedVersion :: Either String Version
validatedVersion :: Either FilePath Version
validatedVersion = do
Version
parsedVersion <- Text -> Either FilePath Version
readVersion Text
str
Bool -> Either FilePath () -> Either FilePath ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Version
parsedVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= Version
lowerOpenApiSpecVersion) Bool -> Bool -> Bool
&& (Version
parsedVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
<= Version
upperOpenApiSpecVersion)) (Either FilePath () -> Either FilePath ())
-> Either FilePath () -> Either FilePath ()
forall a b. (a -> b) -> a -> b
$
FilePath -> Either FilePath ()
forall a b. a -> Either a b
Left (FilePath
"The provided version " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
parsedVersion FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" is out of the allowed range >=" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
lowerOpenApiSpecVersion FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" && <=" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Version -> FilePath
showVersion Version
upperOpenApiSpecVersion)
Version -> Either FilePath Version
forall a. a -> Either FilePath a
forall (m :: * -> *) a. Monad m => a -> m a
return Version
parsedVersion
in
(FilePath -> Parser OpenApiSpecVersion)
-> (Version -> Parser OpenApiSpecVersion)
-> Either FilePath Version
-> Parser OpenApiSpecVersion
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> Parser OpenApiSpecVersion
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (OpenApiSpecVersion -> Parser OpenApiSpecVersion
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (OpenApiSpecVersion -> Parser OpenApiSpecVersion)
-> (Version -> OpenApiSpecVersion)
-> Version
-> Parser OpenApiSpecVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> OpenApiSpecVersion
OpenApiSpecVersion) Either FilePath Version
validatedVersion
where
readVersion :: Text -> Either String Version
readVersion :: Text -> Either FilePath Version
readVersion Text
v = case ReadP Version -> ReadS Version
forall a. ReadP a -> ReadS a
readP_to_S ReadP Version
parseVersion (Text -> FilePath
Text.unpack Text
v) of
[] -> FilePath -> Either FilePath Version
forall a b. a -> Either a b
Left (FilePath -> Either FilePath Version)
-> FilePath -> Either FilePath Version
forall a b. (a -> b) -> a -> b
$ FilePath
"Failed to parse as a version string " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
Text.unpack Text
v
[(Version, FilePath)]
solutions -> Version -> Either FilePath Version
forall a b. b -> Either a b
Right ((Version, FilePath) -> Version
forall a b. (a, b) -> a
fst ((Version, FilePath) -> Version)
-> ([(Version, FilePath)] -> (Version, FilePath))
-> [(Version, FilePath)]
-> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Version, FilePath)] -> (Version, FilePath)
forall a. HasCallStack => [a] -> a
last ([(Version, FilePath)] -> Version)
-> [(Version, FilePath)] -> Version
forall a b. (a -> b) -> a -> b
$ [(Version, FilePath)]
solutions)
instance FromJSON MediaType where
parseJSON :: Value -> Parser MediaType
parseJSON = FilePath -> (Text -> Parser MediaType) -> Value -> Parser MediaType
forall a. FilePath -> (Text -> Parser a) -> Value -> Parser a
withText FilePath
"MediaType" ((Text -> Parser MediaType) -> Value -> Parser MediaType)
-> (Text -> Parser MediaType) -> Value -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ \Text
str ->
Parser MediaType
-> (MediaType -> Parser MediaType)
-> Maybe MediaType
-> Parser MediaType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> Parser MediaType
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser MediaType) -> FilePath -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ FilePath
"Invalid media type literal " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
Text.unpack Text
str) MediaType -> Parser MediaType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe MediaType -> Parser MediaType)
-> Maybe MediaType -> Parser MediaType
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe MediaType
forall a. Accept a => ByteString -> Maybe a
parseAccept (ByteString -> Maybe MediaType) -> ByteString -> Maybe MediaType
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
str
instance FromJSONKey MediaType where
fromJSONKey :: FromJSONKeyFunction MediaType
fromJSONKey = (Text -> Parser MediaType) -> FromJSONKeyFunction MediaType
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser (Value -> Parser MediaType
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser MediaType)
-> (Text -> Value) -> Text -> Parser MediaType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
String)
instance (Eq p, FromJSON p, AesonDefaultValue p) => FromJSON (OAuth2Flow p) where
parseJSON :: Value -> Parser (OAuth2Flow p)
parseJSON = Value -> Parser (OAuth2Flow p)
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON OAuth2Flows where
parseJSON :: Value -> Parser OAuth2Flows
parseJSON = Value -> Parser OAuth2Flows
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON SecuritySchemeType where
parseJSON :: Value -> Parser SecuritySchemeType
parseJSON js :: Value
js@(Object Object
o) = do
(Text
t :: Text) <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
case Text
t of
Text
"http" -> do
Text
scheme <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"scheme"
HttpSchemeType -> SecuritySchemeType
SecuritySchemeHttp (HttpSchemeType -> SecuritySchemeType)
-> Parser HttpSchemeType -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Text
scheme of
Text
"bearer" -> Maybe Text -> HttpSchemeType
HttpSchemeBearer (Maybe Text -> HttpSchemeType)
-> Parser (Maybe Text) -> Parser HttpSchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:! Key
"bearerFormat")
Text
"basic" -> HttpSchemeType -> Parser HttpSchemeType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure HttpSchemeType
HttpSchemeBasic
Text
t -> HttpSchemeType -> Parser HttpSchemeType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HttpSchemeType -> Parser HttpSchemeType)
-> HttpSchemeType -> Parser HttpSchemeType
forall a b. (a -> b) -> a -> b
$ Text -> HttpSchemeType
HttpSchemeCustom Text
t
Text
"apiKey" -> ApiKeyParams -> SecuritySchemeType
SecuritySchemeApiKey (ApiKeyParams -> SecuritySchemeType)
-> Parser ApiKeyParams -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ApiKeyParams
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
Text
"oauth2" -> OAuth2Flows -> SecuritySchemeType
SecuritySchemeOAuth2 (OAuth2Flows -> SecuritySchemeType)
-> Parser OAuth2Flows -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser OAuth2Flows
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"flows")
Text
"openIdConnect" -> URL -> SecuritySchemeType
SecuritySchemeOpenIdConnect (URL -> SecuritySchemeType)
-> Parser URL -> Parser SecuritySchemeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser URL
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"openIdConnectUrl")
Text
_ -> Parser SecuritySchemeType
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
parseJSON Value
_ = Parser SecuritySchemeType
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON OpenApi where
parseJSON :: Value -> Parser OpenApi
parseJSON = Value -> Parser OpenApi
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Server where
parseJSON :: Value -> Parser Server
parseJSON = Value -> Parser Server
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON SecurityScheme where
parseJSON :: Value -> Parser SecurityScheme
parseJSON = Value -> Parser SecurityScheme
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Schema where
parseJSON :: Value -> Parser Schema
parseJSON = (Schema -> Schema) -> Parser Schema -> Parser Schema
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Schema -> Schema
nullaryCleanup (Parser Schema -> Parser Schema)
-> (Value -> Parser Schema) -> Value -> Parser Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Schema
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
where nullaryCleanup :: Schema -> Schema
nullaryCleanup :: Schema -> Schema
nullaryCleanup Schema
s =
if Schema -> Maybe OpenApiItems
_schemaItems Schema
s Maybe OpenApiItems -> Maybe OpenApiItems -> Bool
forall a. Eq a => a -> a -> Bool
== OpenApiItems -> Maybe OpenApiItems
forall a. a -> Maybe a
Just ([Referenced Schema] -> OpenApiItems
OpenApiItemsArray [])
then Schema
s { _schemaExample = Nothing
, _schemaMaxItems = Nothing
}
else Schema
s
instance FromJSON Header where
parseJSON :: Value -> Parser Header
parseJSON = Value -> Parser Header
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON OpenApiItems where
parseJSON :: Value -> Parser OpenApiItems
parseJSON js :: Value
js@(Object Object
obj)
| Object -> Bool
forall a. KeyMap a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Object
obj = OpenApiItems -> Parser OpenApiItems
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OpenApiItems -> Parser OpenApiItems)
-> OpenApiItems -> Parser OpenApiItems
forall a b. (a -> b) -> a -> b
$ [Referenced Schema] -> OpenApiItems
OpenApiItemsArray []
| Bool
otherwise = Referenced Schema -> OpenApiItems
OpenApiItemsObject (Referenced Schema -> OpenApiItems)
-> Parser (Referenced Schema) -> Parser OpenApiItems
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
parseJSON js :: Value
js@(Array Array
_) = [Referenced Schema] -> OpenApiItems
OpenApiItemsArray ([Referenced Schema] -> OpenApiItems)
-> Parser [Referenced Schema] -> Parser OpenApiItems
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Referenced Schema]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
parseJSON Value
_ = Parser OpenApiItems
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON Components where
parseJSON :: Value -> Parser Components
parseJSON = Value -> Parser Components
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON MimeList where
parseJSON :: Value -> Parser MimeList
parseJSON Value
js = [MediaType] -> MimeList
MimeList ([MediaType] -> MimeList)
-> ([FilePath] -> [MediaType]) -> [FilePath] -> MimeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> MediaType) -> [FilePath] -> [MediaType]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> MediaType
forall a. IsString a => FilePath -> a
fromString ([FilePath] -> MimeList) -> Parser [FilePath] -> Parser MimeList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [FilePath]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON Param where
parseJSON :: Value -> Parser Param
parseJSON = Value -> Parser Param
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Responses where
parseJSON :: Value -> Parser Responses
parseJSON (Object Object
o) = Maybe (Referenced Response)
-> InsOrdHashMap Int (Referenced Response) -> Responses
Responses
(Maybe (Referenced Response)
-> InsOrdHashMap Int (Referenced Response) -> Responses)
-> Parser (Maybe (Referenced Response))
-> Parser (InsOrdHashMap Int (Referenced Response) -> Responses)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe (Referenced Response))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default"
Parser (InsOrdHashMap Int (Referenced Response) -> Responses)
-> Parser (InsOrdHashMap Int (Referenced Response))
-> Parser Responses
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser (InsOrdHashMap Int (Referenced Response))
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object (Key -> Object -> Object
forall v. Key -> KeyMap v -> KeyMap v
deleteKey Key
"default" Object
o))
parseJSON Value
_ = Parser Responses
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance FromJSON Example where
parseJSON :: Value -> Parser Example
parseJSON = Value -> Parser Example
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Response where
parseJSON :: Value -> Parser Response
parseJSON = Value -> Parser Response
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Operation where
parseJSON :: Value -> Parser Operation
parseJSON = Value -> Parser Operation
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON PathItem where
parseJSON :: Value -> Parser PathItem
parseJSON = Value -> Parser PathItem
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON SecurityDefinitions where
parseJSON :: Value -> Parser SecurityDefinitions
parseJSON Value
js = Definitions SecurityScheme -> SecurityDefinitions
SecurityDefinitions (Definitions SecurityScheme -> SecurityDefinitions)
-> Parser (Definitions SecurityScheme)
-> Parser SecurityDefinitions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Definitions SecurityScheme)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON RequestBody where
parseJSON :: Value -> Parser RequestBody
parseJSON = Value -> Parser RequestBody
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON MediaTypeObject where
parseJSON :: Value -> Parser MediaTypeObject
parseJSON = Value -> Parser MediaTypeObject
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Encoding where
parseJSON :: Value -> Parser Encoding
parseJSON = Value -> Parser Encoding
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Link where
parseJSON :: Value -> Parser Link
parseJSON = Value -> Parser Link
forall a (xs :: [*]).
(HasDatatypeInfo a, HasSwaggerAesonOptions a,
All2 FromJSON (Code a), All2 Eq (Code a), Code a ~ '[xs]) =>
Value -> Parser a
sopSwaggerGenericParseJSON
instance FromJSON Reference where
parseJSON :: Value -> Parser Reference
parseJSON (Object Object
o) = Text -> Reference
Reference (Text -> Reference) -> Parser Text -> Parser Reference
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"$ref"
parseJSON Value
_ = Parser Reference
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
referencedParseJSON :: FromJSON a => Text -> Value -> JSON.Parser (Referenced a)
referencedParseJSON :: forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
prefix js :: Value
js@(Object Object
o) = do
Maybe Text
ms <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"$ref"
case Maybe Text
ms of
Maybe Text
Nothing -> a -> Referenced a
forall a. a -> Referenced a
Inline (a -> Referenced a) -> Parser a -> Parser (Referenced a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
Just Text
s -> Reference -> Referenced a
forall a. Reference -> Referenced a
Ref (Reference -> Referenced a)
-> Parser Reference -> Parser (Referenced a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Reference
parseRef Text
s
where
parseRef :: Text -> Parser Reference
parseRef Text
s = do
case Text -> Text -> Maybe Text
Text.stripPrefix Text
prefix Text
s of
Maybe Text
Nothing -> FilePath -> Parser Reference
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser Reference) -> FilePath -> Parser Reference
forall a b. (a -> b) -> a -> b
$ FilePath
"expected $ref of the form \"" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
Text.unpack Text
prefix FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"*\", but got " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
forall a. Show a => a -> FilePath
show Text
s
Just Text
suffix -> Reference -> Parser Reference
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Reference
Reference Text
suffix)
referencedParseJSON Text
_ Value
_ = FilePath -> Parser (Referenced a)
forall a. FilePath -> Parser a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"referenceParseJSON: not an object"
instance FromJSON (Referenced Schema) where parseJSON :: Value -> Parser (Referenced Schema)
parseJSON = Text -> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/schemas/"
instance FromJSON (Referenced Param) where parseJSON :: Value -> Parser (Referenced Param)
parseJSON = Text -> Value -> Parser (Referenced Param)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/parameters/"
instance FromJSON (Referenced Response) where parseJSON :: Value -> Parser (Referenced Response)
parseJSON = Text -> Value -> Parser (Referenced Response)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/responses/"
instance FromJSON (Referenced RequestBody) where parseJSON :: Value -> Parser (Referenced RequestBody)
parseJSON = Text -> Value -> Parser (Referenced RequestBody)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/requestBodies/"
instance FromJSON (Referenced Example) where parseJSON :: Value -> Parser (Referenced Example)
parseJSON = Text -> Value -> Parser (Referenced Example)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/examples/"
instance FromJSON (Referenced Header) where parseJSON :: Value -> Parser (Referenced Header)
parseJSON = Text -> Value -> Parser (Referenced Header)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/headers/"
instance FromJSON (Referenced Link) where parseJSON :: Value -> Parser (Referenced Link)
parseJSON = Text -> Value -> Parser (Referenced Link)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/links/"
instance FromJSON (Referenced Callback) where parseJSON :: Value -> Parser (Referenced Callback)
parseJSON = Text -> Value -> Parser (Referenced Callback)
forall a. FromJSON a => Text -> Value -> Parser (Referenced a)
referencedParseJSON Text
"#/components/callbacks/"
instance FromJSON Xml where
parseJSON :: Value -> Parser Xml
parseJSON = Options -> Value -> Parser Xml
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (FilePath -> Options
jsonPrefix FilePath
"xml")
instance FromJSON AdditionalProperties where
parseJSON :: Value -> Parser AdditionalProperties
parseJSON (Bool Bool
b) = AdditionalProperties -> Parser AdditionalProperties
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AdditionalProperties -> Parser AdditionalProperties)
-> AdditionalProperties -> Parser AdditionalProperties
forall a b. (a -> b) -> a -> b
$ Bool -> AdditionalProperties
AdditionalPropertiesAllowed Bool
b
parseJSON Value
js = Referenced Schema -> AdditionalProperties
AdditionalPropertiesSchema (Referenced Schema -> AdditionalProperties)
-> Parser (Referenced Schema) -> Parser AdditionalProperties
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Referenced Schema)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
js
instance FromJSON ExpressionOrValue where
parseJSON :: Value -> Parser ExpressionOrValue
parseJSON (String Text
expr) = ExpressionOrValue -> Parser ExpressionOrValue
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpressionOrValue -> Parser ExpressionOrValue)
-> ExpressionOrValue -> Parser ExpressionOrValue
forall a b. (a -> b) -> a -> b
$ Text -> ExpressionOrValue
Expression Text
expr
parseJSON Value
v = ExpressionOrValue -> Parser ExpressionOrValue
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpressionOrValue -> Parser ExpressionOrValue)
-> ExpressionOrValue -> Parser ExpressionOrValue
forall a b. (a -> b) -> a -> b
$ Value -> ExpressionOrValue
Value Value
v
instance FromJSON Callback where
parseJSON :: Value -> Parser Callback
parseJSON = (InsOrdHashMap Text PathItem -> Callback)
-> Parser (InsOrdHashMap Text PathItem) -> Parser Callback
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InsOrdHashMap Text PathItem -> Callback
Callback (Parser (InsOrdHashMap Text PathItem) -> Parser Callback)
-> (Value -> Parser (InsOrdHashMap Text PathItem))
-> Value
-> Parser Callback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (InsOrdHashMap Text PathItem)
forall a. FromJSON a => Value -> Parser a
parseJSON
instance HasSwaggerAesonOptions Server where
swaggerAesonOptions :: Proxy Server -> SwaggerAesonOptions
swaggerAesonOptions Proxy Server
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"server"
instance HasSwaggerAesonOptions Components where
swaggerAesonOptions :: Proxy Components -> SwaggerAesonOptions
swaggerAesonOptions Proxy Components
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"components"
instance HasSwaggerAesonOptions Header where
swaggerAesonOptions :: Proxy Header -> SwaggerAesonOptions
swaggerAesonOptions Proxy Header
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"header"
instance AesonDefaultValue p => HasSwaggerAesonOptions (OAuth2Flow p) where
swaggerAesonOptions :: Proxy (OAuth2Flow p) -> SwaggerAesonOptions
swaggerAesonOptions Proxy (OAuth2Flow p)
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"oauth2" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"params"
instance HasSwaggerAesonOptions OAuth2Flows where
swaggerAesonOptions :: Proxy OAuth2Flows -> SwaggerAesonOptions
swaggerAesonOptions Proxy OAuth2Flows
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"oauth2Flows"
instance HasSwaggerAesonOptions Operation where
swaggerAesonOptions :: Proxy Operation -> SwaggerAesonOptions
swaggerAesonOptions Proxy Operation
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"operation"
instance HasSwaggerAesonOptions Param where
swaggerAesonOptions :: Proxy Param -> SwaggerAesonOptions
swaggerAesonOptions Proxy Param
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"param"
instance HasSwaggerAesonOptions PathItem where
swaggerAesonOptions :: Proxy PathItem -> SwaggerAesonOptions
swaggerAesonOptions Proxy PathItem
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"pathItem"
instance HasSwaggerAesonOptions Response where
swaggerAesonOptions :: Proxy Response -> SwaggerAesonOptions
swaggerAesonOptions Proxy Response
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"response"
instance HasSwaggerAesonOptions RequestBody where
swaggerAesonOptions :: Proxy RequestBody -> SwaggerAesonOptions
swaggerAesonOptions Proxy RequestBody
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"requestBody"
instance HasSwaggerAesonOptions MediaTypeObject where
swaggerAesonOptions :: Proxy MediaTypeObject -> SwaggerAesonOptions
swaggerAesonOptions Proxy MediaTypeObject
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"mediaTypeObject"
instance HasSwaggerAesonOptions Responses where
swaggerAesonOptions :: Proxy Responses -> SwaggerAesonOptions
swaggerAesonOptions Proxy Responses
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"responses" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"responses"
instance HasSwaggerAesonOptions SecurityScheme where
swaggerAesonOptions :: Proxy SecurityScheme -> SwaggerAesonOptions
swaggerAesonOptions Proxy SecurityScheme
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"securityScheme" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"type"
instance HasSwaggerAesonOptions Schema where
swaggerAesonOptions :: Proxy Schema -> SwaggerAesonOptions
swaggerAesonOptions Proxy Schema
_ = FilePath -> SwaggerAesonOptions
mkSwaggerAesonOptions FilePath
"schema" SwaggerAesonOptions
-> (SwaggerAesonOptions -> SwaggerAesonOptions)
-> SwaggerAesonOptions
forall a b. a -> (a -> b) -> b
& (Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions
Lens' SwaggerAesonOptions (Maybe FilePath)
saoSubObject ((Maybe FilePath -> Identity (Maybe FilePath))
-> SwaggerAesonOptions -> Identity SwaggerAesonOptions)
-> FilePath -> SwaggerAesonOptions -> SwaggerAesonOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ FilePath
"paramSchema"
instance HasSwaggerAesonOptions 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 = Version -> Maybe Version
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 = MimeList -> Maybe MimeList
forall a. a -> Maybe a
Just MimeList
forall a. Monoid a => a
mempty
instance AesonDefaultValue Info
instance AesonDefaultValue ParamLocation
instance AesonDefaultValue Link
instance AesonDefaultValue SecurityDefinitions where
defaultValue :: Maybe SecurityDefinitions
defaultValue = SecurityDefinitions -> Maybe SecurityDefinitions
forall a. a -> Maybe a
Just SecurityDefinitions
forall a. Monoid a => a
mempty