{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AppSync.UpdateGraphqlApi
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a @GraphqlApi@ object.
module Amazonka.AppSync.UpdateGraphqlApi
  ( -- * Creating a Request
    UpdateGraphqlApi (..),
    newUpdateGraphqlApi,

    -- * Request Lenses
    updateGraphqlApi_additionalAuthenticationProviders,
    updateGraphqlApi_authenticationType,
    updateGraphqlApi_lambdaAuthorizerConfig,
    updateGraphqlApi_logConfig,
    updateGraphqlApi_openIDConnectConfig,
    updateGraphqlApi_userPoolConfig,
    updateGraphqlApi_xrayEnabled,
    updateGraphqlApi_apiId,
    updateGraphqlApi_name,

    -- * Destructuring the Response
    UpdateGraphqlApiResponse (..),
    newUpdateGraphqlApiResponse,

    -- * Response Lenses
    updateGraphqlApiResponse_graphqlApi,
    updateGraphqlApiResponse_httpStatus,
  )
where

import Amazonka.AppSync.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateGraphqlApi' smart constructor.
data UpdateGraphqlApi = UpdateGraphqlApi'
  { -- | A list of additional authentication providers for the @GraphqlApi@ API.
    UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders :: Prelude.Maybe [AdditionalAuthenticationProvider],
    -- | The new authentication type for the @GraphqlApi@ object.
    UpdateGraphqlApi -> Maybe AuthenticationType
authenticationType :: Prelude.Maybe AuthenticationType,
    -- | Configuration for Lambda function authorization.
    UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig :: Prelude.Maybe LambdaAuthorizerConfig,
    -- | The Amazon CloudWatch Logs configuration for the @GraphqlApi@ object.
    UpdateGraphqlApi -> Maybe LogConfig
logConfig :: Prelude.Maybe LogConfig,
    -- | The OpenID Connect configuration for the @GraphqlApi@ object.
    UpdateGraphqlApi -> Maybe OpenIDConnectConfig
openIDConnectConfig :: Prelude.Maybe OpenIDConnectConfig,
    -- | The new Amazon Cognito user pool configuration for the @~GraphqlApi@
    -- object.
    UpdateGraphqlApi -> Maybe UserPoolConfig
userPoolConfig :: Prelude.Maybe UserPoolConfig,
    -- | A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
    UpdateGraphqlApi -> Maybe Bool
xrayEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The API ID.
    UpdateGraphqlApi -> Text
apiId :: Prelude.Text,
    -- | The new name for the @GraphqlApi@ object.
    UpdateGraphqlApi -> Text
name :: Prelude.Text
  }
  deriving (UpdateGraphqlApi -> UpdateGraphqlApi -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGraphqlApi -> UpdateGraphqlApi -> Bool
$c/= :: UpdateGraphqlApi -> UpdateGraphqlApi -> Bool
== :: UpdateGraphqlApi -> UpdateGraphqlApi -> Bool
$c== :: UpdateGraphqlApi -> UpdateGraphqlApi -> Bool
Prelude.Eq, ReadPrec [UpdateGraphqlApi]
ReadPrec UpdateGraphqlApi
Int -> ReadS UpdateGraphqlApi
ReadS [UpdateGraphqlApi]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGraphqlApi]
$creadListPrec :: ReadPrec [UpdateGraphqlApi]
readPrec :: ReadPrec UpdateGraphqlApi
$creadPrec :: ReadPrec UpdateGraphqlApi
readList :: ReadS [UpdateGraphqlApi]
$creadList :: ReadS [UpdateGraphqlApi]
readsPrec :: Int -> ReadS UpdateGraphqlApi
$creadsPrec :: Int -> ReadS UpdateGraphqlApi
Prelude.Read, Int -> UpdateGraphqlApi -> ShowS
[UpdateGraphqlApi] -> ShowS
UpdateGraphqlApi -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGraphqlApi] -> ShowS
$cshowList :: [UpdateGraphqlApi] -> ShowS
show :: UpdateGraphqlApi -> String
$cshow :: UpdateGraphqlApi -> String
showsPrec :: Int -> UpdateGraphqlApi -> ShowS
$cshowsPrec :: Int -> UpdateGraphqlApi -> ShowS
Prelude.Show, forall x. Rep UpdateGraphqlApi x -> UpdateGraphqlApi
forall x. UpdateGraphqlApi -> Rep UpdateGraphqlApi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateGraphqlApi x -> UpdateGraphqlApi
$cfrom :: forall x. UpdateGraphqlApi -> Rep UpdateGraphqlApi x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGraphqlApi' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'additionalAuthenticationProviders', 'updateGraphqlApi_additionalAuthenticationProviders' - A list of additional authentication providers for the @GraphqlApi@ API.
--
-- 'authenticationType', 'updateGraphqlApi_authenticationType' - The new authentication type for the @GraphqlApi@ object.
--
-- 'lambdaAuthorizerConfig', 'updateGraphqlApi_lambdaAuthorizerConfig' - Configuration for Lambda function authorization.
--
-- 'logConfig', 'updateGraphqlApi_logConfig' - The Amazon CloudWatch Logs configuration for the @GraphqlApi@ object.
--
-- 'openIDConnectConfig', 'updateGraphqlApi_openIDConnectConfig' - The OpenID Connect configuration for the @GraphqlApi@ object.
--
-- 'userPoolConfig', 'updateGraphqlApi_userPoolConfig' - The new Amazon Cognito user pool configuration for the @~GraphqlApi@
-- object.
--
-- 'xrayEnabled', 'updateGraphqlApi_xrayEnabled' - A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
--
-- 'apiId', 'updateGraphqlApi_apiId' - The API ID.
--
-- 'name', 'updateGraphqlApi_name' - The new name for the @GraphqlApi@ object.
newUpdateGraphqlApi ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  UpdateGraphqlApi
newUpdateGraphqlApi :: Text -> Text -> UpdateGraphqlApi
newUpdateGraphqlApi Text
pApiId_ Text
pName_ =
  UpdateGraphqlApi'
    { $sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationType:UpdateGraphqlApi' :: Maybe AuthenticationType
authenticationType = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfig:UpdateGraphqlApi' :: Maybe LogConfig
logConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:openIDConnectConfig:UpdateGraphqlApi' :: Maybe OpenIDConnectConfig
openIDConnectConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolConfig:UpdateGraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:xrayEnabled:UpdateGraphqlApi' :: Maybe Bool
xrayEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:apiId:UpdateGraphqlApi' :: Text
apiId = Text
pApiId_,
      $sel:name:UpdateGraphqlApi' :: Text
name = Text
pName_
    }

-- | A list of additional authentication providers for the @GraphqlApi@ API.
updateGraphqlApi_additionalAuthenticationProviders :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe [AdditionalAuthenticationProvider])
updateGraphqlApi_additionalAuthenticationProviders :: Lens' UpdateGraphqlApi (Maybe [AdditionalAuthenticationProvider])
updateGraphqlApi_additionalAuthenticationProviders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders} -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe [AdditionalAuthenticationProvider]
a -> UpdateGraphqlApi
s {$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders = Maybe [AdditionalAuthenticationProvider]
a} :: UpdateGraphqlApi) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The new authentication type for the @GraphqlApi@ object.
updateGraphqlApi_authenticationType :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe AuthenticationType)
updateGraphqlApi_authenticationType :: Lens' UpdateGraphqlApi (Maybe AuthenticationType)
updateGraphqlApi_authenticationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe AuthenticationType
authenticationType :: Maybe AuthenticationType
$sel:authenticationType:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe AuthenticationType
authenticationType} -> Maybe AuthenticationType
authenticationType) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe AuthenticationType
a -> UpdateGraphqlApi
s {$sel:authenticationType:UpdateGraphqlApi' :: Maybe AuthenticationType
authenticationType = Maybe AuthenticationType
a} :: UpdateGraphqlApi)

-- | Configuration for Lambda function authorization.
updateGraphqlApi_lambdaAuthorizerConfig :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe LambdaAuthorizerConfig)
updateGraphqlApi_lambdaAuthorizerConfig :: Lens' UpdateGraphqlApi (Maybe LambdaAuthorizerConfig)
updateGraphqlApi_lambdaAuthorizerConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig} -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe LambdaAuthorizerConfig
a -> UpdateGraphqlApi
s {$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig = Maybe LambdaAuthorizerConfig
a} :: UpdateGraphqlApi)

-- | The Amazon CloudWatch Logs configuration for the @GraphqlApi@ object.
updateGraphqlApi_logConfig :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe LogConfig)
updateGraphqlApi_logConfig :: Lens' UpdateGraphqlApi (Maybe LogConfig)
updateGraphqlApi_logConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe LogConfig
logConfig :: Maybe LogConfig
$sel:logConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LogConfig
logConfig} -> Maybe LogConfig
logConfig) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe LogConfig
a -> UpdateGraphqlApi
s {$sel:logConfig:UpdateGraphqlApi' :: Maybe LogConfig
logConfig = Maybe LogConfig
a} :: UpdateGraphqlApi)

-- | The OpenID Connect configuration for the @GraphqlApi@ object.
updateGraphqlApi_openIDConnectConfig :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe OpenIDConnectConfig)
updateGraphqlApi_openIDConnectConfig :: Lens' UpdateGraphqlApi (Maybe OpenIDConnectConfig)
updateGraphqlApi_openIDConnectConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe OpenIDConnectConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
$sel:openIDConnectConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe OpenIDConnectConfig
openIDConnectConfig} -> Maybe OpenIDConnectConfig
openIDConnectConfig) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe OpenIDConnectConfig
a -> UpdateGraphqlApi
s {$sel:openIDConnectConfig:UpdateGraphqlApi' :: Maybe OpenIDConnectConfig
openIDConnectConfig = Maybe OpenIDConnectConfig
a} :: UpdateGraphqlApi)

-- | The new Amazon Cognito user pool configuration for the @~GraphqlApi@
-- object.
updateGraphqlApi_userPoolConfig :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe UserPoolConfig)
updateGraphqlApi_userPoolConfig :: Lens' UpdateGraphqlApi (Maybe UserPoolConfig)
updateGraphqlApi_userPoolConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe UserPoolConfig
userPoolConfig :: Maybe UserPoolConfig
$sel:userPoolConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe UserPoolConfig
userPoolConfig} -> Maybe UserPoolConfig
userPoolConfig) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe UserPoolConfig
a -> UpdateGraphqlApi
s {$sel:userPoolConfig:UpdateGraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = Maybe UserPoolConfig
a} :: UpdateGraphqlApi)

-- | A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
updateGraphqlApi_xrayEnabled :: Lens.Lens' UpdateGraphqlApi (Prelude.Maybe Prelude.Bool)
updateGraphqlApi_xrayEnabled :: Lens' UpdateGraphqlApi (Maybe Bool)
updateGraphqlApi_xrayEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Maybe Bool
xrayEnabled :: Maybe Bool
$sel:xrayEnabled:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe Bool
xrayEnabled} -> Maybe Bool
xrayEnabled) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Maybe Bool
a -> UpdateGraphqlApi
s {$sel:xrayEnabled:UpdateGraphqlApi' :: Maybe Bool
xrayEnabled = Maybe Bool
a} :: UpdateGraphqlApi)

-- | The API ID.
updateGraphqlApi_apiId :: Lens.Lens' UpdateGraphqlApi Prelude.Text
updateGraphqlApi_apiId :: Lens' UpdateGraphqlApi Text
updateGraphqlApi_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Text
apiId :: Text
$sel:apiId:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
apiId} -> Text
apiId) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Text
a -> UpdateGraphqlApi
s {$sel:apiId:UpdateGraphqlApi' :: Text
apiId = Text
a} :: UpdateGraphqlApi)

-- | The new name for the @GraphqlApi@ object.
updateGraphqlApi_name :: Lens.Lens' UpdateGraphqlApi Prelude.Text
updateGraphqlApi_name :: Lens' UpdateGraphqlApi Text
updateGraphqlApi_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApi' {Text
name :: Text
$sel:name:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
name} -> Text
name) (\s :: UpdateGraphqlApi
s@UpdateGraphqlApi' {} Text
a -> UpdateGraphqlApi
s {$sel:name:UpdateGraphqlApi' :: Text
name = Text
a} :: UpdateGraphqlApi)

instance Core.AWSRequest UpdateGraphqlApi where
  type
    AWSResponse UpdateGraphqlApi =
      UpdateGraphqlApiResponse
  request :: (Service -> Service)
-> UpdateGraphqlApi -> Request UpdateGraphqlApi
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateGraphqlApi
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateGraphqlApi)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe GraphqlApi -> Int -> UpdateGraphqlApiResponse
UpdateGraphqlApiResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"graphqlApi")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateGraphqlApi where
  hashWithSalt :: Int -> UpdateGraphqlApi -> Int
hashWithSalt Int
_salt UpdateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe AuthenticationType
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
name :: Text
apiId :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
authenticationType :: Maybe AuthenticationType
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:name:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:apiId:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:xrayEnabled:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe UserPoolConfig
$sel:openIDConnectConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:authenticationType:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe AuthenticationType
$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationType
authenticationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogConfig
logConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenIDConnectConfig
openIDConnectConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolConfig
userPoolConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
xrayEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
apiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData UpdateGraphqlApi where
  rnf :: UpdateGraphqlApi -> ()
rnf UpdateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe AuthenticationType
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
name :: Text
apiId :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
authenticationType :: Maybe AuthenticationType
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:name:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:apiId:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:xrayEnabled:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe UserPoolConfig
$sel:openIDConnectConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:authenticationType:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe AuthenticationType
$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationType
authenticationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogConfig
logConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpenIDConnectConfig
openIDConnectConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserPoolConfig
userPoolConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
xrayEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders UpdateGraphqlApi where
  toHeaders :: UpdateGraphqlApi -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateGraphqlApi where
  toJSON :: UpdateGraphqlApi -> Value
toJSON UpdateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe AuthenticationType
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
name :: Text
apiId :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
authenticationType :: Maybe AuthenticationType
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:name:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:apiId:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:xrayEnabled:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe UserPoolConfig
$sel:openIDConnectConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:authenticationType:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe AuthenticationType
$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"additionalAuthenticationProviders" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders,
            (Key
"authenticationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AuthenticationType
authenticationType,
            (Key
"lambdaAuthorizerConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig,
            (Key
"logConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LogConfig
logConfig,
            (Key
"openIDConnectConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OpenIDConnectConfig
openIDConnectConfig,
            (Key
"userPoolConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserPoolConfig
userPoolConfig,
            (Key
"xrayEnabled" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
xrayEnabled,
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

instance Data.ToPath UpdateGraphqlApi where
  toPath :: UpdateGraphqlApi -> ByteString
toPath UpdateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe AuthenticationType
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
name :: Text
apiId :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
authenticationType :: Maybe AuthenticationType
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:name:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:apiId:UpdateGraphqlApi' :: UpdateGraphqlApi -> Text
$sel:xrayEnabled:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe UserPoolConfig
$sel:openIDConnectConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:authenticationType:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe AuthenticationType
$sel:additionalAuthenticationProviders:UpdateGraphqlApi' :: UpdateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/v1/apis/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId]

instance Data.ToQuery UpdateGraphqlApi where
  toQuery :: UpdateGraphqlApi -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateGraphqlApiResponse' smart constructor.
data UpdateGraphqlApiResponse = UpdateGraphqlApiResponse'
  { -- | The updated @GraphqlApi@ object.
    UpdateGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi :: Prelude.Maybe GraphqlApi,
    -- | The response's http status code.
    UpdateGraphqlApiResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateGraphqlApiResponse -> UpdateGraphqlApiResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGraphqlApiResponse -> UpdateGraphqlApiResponse -> Bool
$c/= :: UpdateGraphqlApiResponse -> UpdateGraphqlApiResponse -> Bool
== :: UpdateGraphqlApiResponse -> UpdateGraphqlApiResponse -> Bool
$c== :: UpdateGraphqlApiResponse -> UpdateGraphqlApiResponse -> Bool
Prelude.Eq, ReadPrec [UpdateGraphqlApiResponse]
ReadPrec UpdateGraphqlApiResponse
Int -> ReadS UpdateGraphqlApiResponse
ReadS [UpdateGraphqlApiResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGraphqlApiResponse]
$creadListPrec :: ReadPrec [UpdateGraphqlApiResponse]
readPrec :: ReadPrec UpdateGraphqlApiResponse
$creadPrec :: ReadPrec UpdateGraphqlApiResponse
readList :: ReadS [UpdateGraphqlApiResponse]
$creadList :: ReadS [UpdateGraphqlApiResponse]
readsPrec :: Int -> ReadS UpdateGraphqlApiResponse
$creadsPrec :: Int -> ReadS UpdateGraphqlApiResponse
Prelude.Read, Int -> UpdateGraphqlApiResponse -> ShowS
[UpdateGraphqlApiResponse] -> ShowS
UpdateGraphqlApiResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGraphqlApiResponse] -> ShowS
$cshowList :: [UpdateGraphqlApiResponse] -> ShowS
show :: UpdateGraphqlApiResponse -> String
$cshow :: UpdateGraphqlApiResponse -> String
showsPrec :: Int -> UpdateGraphqlApiResponse -> ShowS
$cshowsPrec :: Int -> UpdateGraphqlApiResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateGraphqlApiResponse x -> UpdateGraphqlApiResponse
forall x.
UpdateGraphqlApiResponse -> Rep UpdateGraphqlApiResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateGraphqlApiResponse x -> UpdateGraphqlApiResponse
$cfrom :: forall x.
UpdateGraphqlApiResponse -> Rep UpdateGraphqlApiResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGraphqlApiResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'graphqlApi', 'updateGraphqlApiResponse_graphqlApi' - The updated @GraphqlApi@ object.
--
-- 'httpStatus', 'updateGraphqlApiResponse_httpStatus' - The response's http status code.
newUpdateGraphqlApiResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateGraphqlApiResponse
newUpdateGraphqlApiResponse :: Int -> UpdateGraphqlApiResponse
newUpdateGraphqlApiResponse Int
pHttpStatus_ =
  UpdateGraphqlApiResponse'
    { $sel:graphqlApi:UpdateGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGraphqlApiResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The updated @GraphqlApi@ object.
updateGraphqlApiResponse_graphqlApi :: Lens.Lens' UpdateGraphqlApiResponse (Prelude.Maybe GraphqlApi)
updateGraphqlApiResponse_graphqlApi :: Lens' UpdateGraphqlApiResponse (Maybe GraphqlApi)
updateGraphqlApiResponse_graphqlApi = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApiResponse' {Maybe GraphqlApi
graphqlApi :: Maybe GraphqlApi
$sel:graphqlApi:UpdateGraphqlApiResponse' :: UpdateGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi} -> Maybe GraphqlApi
graphqlApi) (\s :: UpdateGraphqlApiResponse
s@UpdateGraphqlApiResponse' {} Maybe GraphqlApi
a -> UpdateGraphqlApiResponse
s {$sel:graphqlApi:UpdateGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi = Maybe GraphqlApi
a} :: UpdateGraphqlApiResponse)

-- | The response's http status code.
updateGraphqlApiResponse_httpStatus :: Lens.Lens' UpdateGraphqlApiResponse Prelude.Int
updateGraphqlApiResponse_httpStatus :: Lens' UpdateGraphqlApiResponse Int
updateGraphqlApiResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGraphqlApiResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateGraphqlApiResponse' :: UpdateGraphqlApiResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateGraphqlApiResponse
s@UpdateGraphqlApiResponse' {} Int
a -> UpdateGraphqlApiResponse
s {$sel:httpStatus:UpdateGraphqlApiResponse' :: Int
httpStatus = Int
a} :: UpdateGraphqlApiResponse)

instance Prelude.NFData UpdateGraphqlApiResponse where
  rnf :: UpdateGraphqlApiResponse -> ()
rnf UpdateGraphqlApiResponse' {Int
Maybe GraphqlApi
httpStatus :: Int
graphqlApi :: Maybe GraphqlApi
$sel:httpStatus:UpdateGraphqlApiResponse' :: UpdateGraphqlApiResponse -> Int
$sel:graphqlApi:UpdateGraphqlApiResponse' :: UpdateGraphqlApiResponse -> Maybe GraphqlApi
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GraphqlApi
graphqlApi
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus