{-# 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.AmplifyBackend.UpdateBackendConfig
-- 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 the AWS resources required to access the Amplify Admin UI.
module Amazonka.AmplifyBackend.UpdateBackendConfig
  ( -- * Creating a Request
    UpdateBackendConfig (..),
    newUpdateBackendConfig,

    -- * Request Lenses
    updateBackendConfig_loginAuthConfig,
    updateBackendConfig_appId,

    -- * Destructuring the Response
    UpdateBackendConfigResponse (..),
    newUpdateBackendConfigResponse,

    -- * Response Lenses
    updateBackendConfigResponse_appId,
    updateBackendConfigResponse_backendManagerAppId,
    updateBackendConfigResponse_error,
    updateBackendConfigResponse_loginAuthConfig,
    updateBackendConfigResponse_httpStatus,
  )
where

import Amazonka.AmplifyBackend.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

-- | The request body for UpdateBackendConfig.
--
-- /See:/ 'newUpdateBackendConfig' smart constructor.
data UpdateBackendConfig = UpdateBackendConfig'
  { -- | Describes the Amazon Cognito configuration for Admin UI access.
    UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
loginAuthConfig :: Prelude.Maybe LoginAuthConfigReqObj,
    -- | The app ID.
    UpdateBackendConfig -> Text
appId :: Prelude.Text
  }
  deriving (UpdateBackendConfig -> UpdateBackendConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBackendConfig -> UpdateBackendConfig -> Bool
$c/= :: UpdateBackendConfig -> UpdateBackendConfig -> Bool
== :: UpdateBackendConfig -> UpdateBackendConfig -> Bool
$c== :: UpdateBackendConfig -> UpdateBackendConfig -> Bool
Prelude.Eq, ReadPrec [UpdateBackendConfig]
ReadPrec UpdateBackendConfig
Int -> ReadS UpdateBackendConfig
ReadS [UpdateBackendConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBackendConfig]
$creadListPrec :: ReadPrec [UpdateBackendConfig]
readPrec :: ReadPrec UpdateBackendConfig
$creadPrec :: ReadPrec UpdateBackendConfig
readList :: ReadS [UpdateBackendConfig]
$creadList :: ReadS [UpdateBackendConfig]
readsPrec :: Int -> ReadS UpdateBackendConfig
$creadsPrec :: Int -> ReadS UpdateBackendConfig
Prelude.Read, Int -> UpdateBackendConfig -> ShowS
[UpdateBackendConfig] -> ShowS
UpdateBackendConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBackendConfig] -> ShowS
$cshowList :: [UpdateBackendConfig] -> ShowS
show :: UpdateBackendConfig -> String
$cshow :: UpdateBackendConfig -> String
showsPrec :: Int -> UpdateBackendConfig -> ShowS
$cshowsPrec :: Int -> UpdateBackendConfig -> ShowS
Prelude.Show, forall x. Rep UpdateBackendConfig x -> UpdateBackendConfig
forall x. UpdateBackendConfig -> Rep UpdateBackendConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateBackendConfig x -> UpdateBackendConfig
$cfrom :: forall x. UpdateBackendConfig -> Rep UpdateBackendConfig x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBackendConfig' 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:
--
-- 'loginAuthConfig', 'updateBackendConfig_loginAuthConfig' - Describes the Amazon Cognito configuration for Admin UI access.
--
-- 'appId', 'updateBackendConfig_appId' - The app ID.
newUpdateBackendConfig ::
  -- | 'appId'
  Prelude.Text ->
  UpdateBackendConfig
newUpdateBackendConfig :: Text -> UpdateBackendConfig
newUpdateBackendConfig Text
pAppId_ =
  UpdateBackendConfig'
    { $sel:loginAuthConfig:UpdateBackendConfig' :: Maybe LoginAuthConfigReqObj
loginAuthConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:appId:UpdateBackendConfig' :: Text
appId = Text
pAppId_
    }

-- | Describes the Amazon Cognito configuration for Admin UI access.
updateBackendConfig_loginAuthConfig :: Lens.Lens' UpdateBackendConfig (Prelude.Maybe LoginAuthConfigReqObj)
updateBackendConfig_loginAuthConfig :: Lens' UpdateBackendConfig (Maybe LoginAuthConfigReqObj)
updateBackendConfig_loginAuthConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfig' {Maybe LoginAuthConfigReqObj
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:loginAuthConfig:UpdateBackendConfig' :: UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
loginAuthConfig} -> Maybe LoginAuthConfigReqObj
loginAuthConfig) (\s :: UpdateBackendConfig
s@UpdateBackendConfig' {} Maybe LoginAuthConfigReqObj
a -> UpdateBackendConfig
s {$sel:loginAuthConfig:UpdateBackendConfig' :: Maybe LoginAuthConfigReqObj
loginAuthConfig = Maybe LoginAuthConfigReqObj
a} :: UpdateBackendConfig)

-- | The app ID.
updateBackendConfig_appId :: Lens.Lens' UpdateBackendConfig Prelude.Text
updateBackendConfig_appId :: Lens' UpdateBackendConfig Text
updateBackendConfig_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfig' {Text
appId :: Text
$sel:appId:UpdateBackendConfig' :: UpdateBackendConfig -> Text
appId} -> Text
appId) (\s :: UpdateBackendConfig
s@UpdateBackendConfig' {} Text
a -> UpdateBackendConfig
s {$sel:appId:UpdateBackendConfig' :: Text
appId = Text
a} :: UpdateBackendConfig)

instance Core.AWSRequest UpdateBackendConfig where
  type
    AWSResponse UpdateBackendConfig =
      UpdateBackendConfigResponse
  request :: (Service -> Service)
-> UpdateBackendConfig -> Request UpdateBackendConfig
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 UpdateBackendConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateBackendConfig)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe LoginAuthConfigReqObj
-> Int
-> UpdateBackendConfigResponse
UpdateBackendConfigResponse'
            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
"appId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"backendManagerAppId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"error")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"loginAuthConfig")
            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 UpdateBackendConfig where
  hashWithSalt :: Int -> UpdateBackendConfig -> Int
hashWithSalt Int
_salt UpdateBackendConfig' {Maybe LoginAuthConfigReqObj
Text
appId :: Text
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:appId:UpdateBackendConfig' :: UpdateBackendConfig -> Text
$sel:loginAuthConfig:UpdateBackendConfig' :: UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoginAuthConfigReqObj
loginAuthConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId

instance Prelude.NFData UpdateBackendConfig where
  rnf :: UpdateBackendConfig -> ()
rnf UpdateBackendConfig' {Maybe LoginAuthConfigReqObj
Text
appId :: Text
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:appId:UpdateBackendConfig' :: UpdateBackendConfig -> Text
$sel:loginAuthConfig:UpdateBackendConfig' :: UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LoginAuthConfigReqObj
loginAuthConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId

instance Data.ToHeaders UpdateBackendConfig where
  toHeaders :: UpdateBackendConfig -> 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 UpdateBackendConfig where
  toJSON :: UpdateBackendConfig -> Value
toJSON UpdateBackendConfig' {Maybe LoginAuthConfigReqObj
Text
appId :: Text
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:appId:UpdateBackendConfig' :: UpdateBackendConfig -> Text
$sel:loginAuthConfig:UpdateBackendConfig' :: UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"loginAuthConfig" 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 LoginAuthConfigReqObj
loginAuthConfig
          ]
      )

instance Data.ToPath UpdateBackendConfig where
  toPath :: UpdateBackendConfig -> ByteString
toPath UpdateBackendConfig' {Maybe LoginAuthConfigReqObj
Text
appId :: Text
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:appId:UpdateBackendConfig' :: UpdateBackendConfig -> Text
$sel:loginAuthConfig:UpdateBackendConfig' :: UpdateBackendConfig -> Maybe LoginAuthConfigReqObj
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/backend/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId, ByteString
"/config/update"]

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

-- | /See:/ 'newUpdateBackendConfigResponse' smart constructor.
data UpdateBackendConfigResponse = UpdateBackendConfigResponse'
  { -- | The app ID.
    UpdateBackendConfigResponse -> Maybe Text
appId :: Prelude.Maybe Prelude.Text,
    -- | The app ID for the backend manager.
    UpdateBackendConfigResponse -> Maybe Text
backendManagerAppId :: Prelude.Maybe Prelude.Text,
    -- | If the request fails, this error is returned.
    UpdateBackendConfigResponse -> Maybe Text
error :: Prelude.Maybe Prelude.Text,
    -- | Describes the Amazon Cognito configurations for the Admin UI auth
    -- resource to log in with.
    UpdateBackendConfigResponse -> Maybe LoginAuthConfigReqObj
loginAuthConfig :: Prelude.Maybe LoginAuthConfigReqObj,
    -- | The response's http status code.
    UpdateBackendConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateBackendConfigResponse -> UpdateBackendConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBackendConfigResponse -> UpdateBackendConfigResponse -> Bool
$c/= :: UpdateBackendConfigResponse -> UpdateBackendConfigResponse -> Bool
== :: UpdateBackendConfigResponse -> UpdateBackendConfigResponse -> Bool
$c== :: UpdateBackendConfigResponse -> UpdateBackendConfigResponse -> Bool
Prelude.Eq, ReadPrec [UpdateBackendConfigResponse]
ReadPrec UpdateBackendConfigResponse
Int -> ReadS UpdateBackendConfigResponse
ReadS [UpdateBackendConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBackendConfigResponse]
$creadListPrec :: ReadPrec [UpdateBackendConfigResponse]
readPrec :: ReadPrec UpdateBackendConfigResponse
$creadPrec :: ReadPrec UpdateBackendConfigResponse
readList :: ReadS [UpdateBackendConfigResponse]
$creadList :: ReadS [UpdateBackendConfigResponse]
readsPrec :: Int -> ReadS UpdateBackendConfigResponse
$creadsPrec :: Int -> ReadS UpdateBackendConfigResponse
Prelude.Read, Int -> UpdateBackendConfigResponse -> ShowS
[UpdateBackendConfigResponse] -> ShowS
UpdateBackendConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBackendConfigResponse] -> ShowS
$cshowList :: [UpdateBackendConfigResponse] -> ShowS
show :: UpdateBackendConfigResponse -> String
$cshow :: UpdateBackendConfigResponse -> String
showsPrec :: Int -> UpdateBackendConfigResponse -> ShowS
$cshowsPrec :: Int -> UpdateBackendConfigResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateBackendConfigResponse x -> UpdateBackendConfigResponse
forall x.
UpdateBackendConfigResponse -> Rep UpdateBackendConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateBackendConfigResponse x -> UpdateBackendConfigResponse
$cfrom :: forall x.
UpdateBackendConfigResponse -> Rep UpdateBackendConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBackendConfigResponse' 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:
--
-- 'appId', 'updateBackendConfigResponse_appId' - The app ID.
--
-- 'backendManagerAppId', 'updateBackendConfigResponse_backendManagerAppId' - The app ID for the backend manager.
--
-- 'error', 'updateBackendConfigResponse_error' - If the request fails, this error is returned.
--
-- 'loginAuthConfig', 'updateBackendConfigResponse_loginAuthConfig' - Describes the Amazon Cognito configurations for the Admin UI auth
-- resource to log in with.
--
-- 'httpStatus', 'updateBackendConfigResponse_httpStatus' - The response's http status code.
newUpdateBackendConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateBackendConfigResponse
newUpdateBackendConfigResponse :: Int -> UpdateBackendConfigResponse
newUpdateBackendConfigResponse Int
pHttpStatus_ =
  UpdateBackendConfigResponse'
    { $sel:appId:UpdateBackendConfigResponse' :: Maybe Text
appId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:backendManagerAppId:UpdateBackendConfigResponse' :: Maybe Text
backendManagerAppId = forall a. Maybe a
Prelude.Nothing,
      $sel:error:UpdateBackendConfigResponse' :: Maybe Text
error = forall a. Maybe a
Prelude.Nothing,
      $sel:loginAuthConfig:UpdateBackendConfigResponse' :: Maybe LoginAuthConfigReqObj
loginAuthConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateBackendConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The app ID.
updateBackendConfigResponse_appId :: Lens.Lens' UpdateBackendConfigResponse (Prelude.Maybe Prelude.Text)
updateBackendConfigResponse_appId :: Lens' UpdateBackendConfigResponse (Maybe Text)
updateBackendConfigResponse_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfigResponse' {Maybe Text
appId :: Maybe Text
$sel:appId:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
appId} -> Maybe Text
appId) (\s :: UpdateBackendConfigResponse
s@UpdateBackendConfigResponse' {} Maybe Text
a -> UpdateBackendConfigResponse
s {$sel:appId:UpdateBackendConfigResponse' :: Maybe Text
appId = Maybe Text
a} :: UpdateBackendConfigResponse)

-- | The app ID for the backend manager.
updateBackendConfigResponse_backendManagerAppId :: Lens.Lens' UpdateBackendConfigResponse (Prelude.Maybe Prelude.Text)
updateBackendConfigResponse_backendManagerAppId :: Lens' UpdateBackendConfigResponse (Maybe Text)
updateBackendConfigResponse_backendManagerAppId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfigResponse' {Maybe Text
backendManagerAppId :: Maybe Text
$sel:backendManagerAppId:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
backendManagerAppId} -> Maybe Text
backendManagerAppId) (\s :: UpdateBackendConfigResponse
s@UpdateBackendConfigResponse' {} Maybe Text
a -> UpdateBackendConfigResponse
s {$sel:backendManagerAppId:UpdateBackendConfigResponse' :: Maybe Text
backendManagerAppId = Maybe Text
a} :: UpdateBackendConfigResponse)

-- | If the request fails, this error is returned.
updateBackendConfigResponse_error :: Lens.Lens' UpdateBackendConfigResponse (Prelude.Maybe Prelude.Text)
updateBackendConfigResponse_error :: Lens' UpdateBackendConfigResponse (Maybe Text)
updateBackendConfigResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfigResponse' {Maybe Text
error :: Maybe Text
$sel:error:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
error} -> Maybe Text
error) (\s :: UpdateBackendConfigResponse
s@UpdateBackendConfigResponse' {} Maybe Text
a -> UpdateBackendConfigResponse
s {$sel:error:UpdateBackendConfigResponse' :: Maybe Text
error = Maybe Text
a} :: UpdateBackendConfigResponse)

-- | Describes the Amazon Cognito configurations for the Admin UI auth
-- resource to log in with.
updateBackendConfigResponse_loginAuthConfig :: Lens.Lens' UpdateBackendConfigResponse (Prelude.Maybe LoginAuthConfigReqObj)
updateBackendConfigResponse_loginAuthConfig :: Lens' UpdateBackendConfigResponse (Maybe LoginAuthConfigReqObj)
updateBackendConfigResponse_loginAuthConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBackendConfigResponse' {Maybe LoginAuthConfigReqObj
loginAuthConfig :: Maybe LoginAuthConfigReqObj
$sel:loginAuthConfig:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe LoginAuthConfigReqObj
loginAuthConfig} -> Maybe LoginAuthConfigReqObj
loginAuthConfig) (\s :: UpdateBackendConfigResponse
s@UpdateBackendConfigResponse' {} Maybe LoginAuthConfigReqObj
a -> UpdateBackendConfigResponse
s {$sel:loginAuthConfig:UpdateBackendConfigResponse' :: Maybe LoginAuthConfigReqObj
loginAuthConfig = Maybe LoginAuthConfigReqObj
a} :: UpdateBackendConfigResponse)

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

instance Prelude.NFData UpdateBackendConfigResponse where
  rnf :: UpdateBackendConfigResponse -> ()
rnf UpdateBackendConfigResponse' {Int
Maybe Text
Maybe LoginAuthConfigReqObj
httpStatus :: Int
loginAuthConfig :: Maybe LoginAuthConfigReqObj
error :: Maybe Text
backendManagerAppId :: Maybe Text
appId :: Maybe Text
$sel:httpStatus:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Int
$sel:loginAuthConfig:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe LoginAuthConfigReqObj
$sel:error:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
$sel:backendManagerAppId:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
$sel:appId:UpdateBackendConfigResponse' :: UpdateBackendConfigResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backendManagerAppId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
error
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoginAuthConfigReqObj
loginAuthConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus