{-# 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.Kafka.BatchDisassociateScramSecret
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates one or more Scram Secrets from an Amazon MSK cluster.
module Amazonka.Kafka.BatchDisassociateScramSecret
  ( -- * Creating a Request
    BatchDisassociateScramSecret (..),
    newBatchDisassociateScramSecret,

    -- * Request Lenses
    batchDisassociateScramSecret_clusterArn,
    batchDisassociateScramSecret_secretArnList,

    -- * Destructuring the Response
    BatchDisassociateScramSecretResponse (..),
    newBatchDisassociateScramSecretResponse,

    -- * Response Lenses
    batchDisassociateScramSecretResponse_clusterArn,
    batchDisassociateScramSecretResponse_unprocessedScramSecrets,
    batchDisassociateScramSecretResponse_httpStatus,
  )
where

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

-- | Disassociates sasl scram secrets to cluster.
--
-- /See:/ 'newBatchDisassociateScramSecret' smart constructor.
data BatchDisassociateScramSecret = BatchDisassociateScramSecret'
  { -- | The Amazon Resource Name (ARN) of the cluster to be updated.
    BatchDisassociateScramSecret -> Text
clusterArn :: Prelude.Text,
    -- | List of AWS Secrets Manager secret ARNs.
    BatchDisassociateScramSecret -> [Text]
secretArnList :: [Prelude.Text]
  }
  deriving (BatchDisassociateScramSecret
-> BatchDisassociateScramSecret -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDisassociateScramSecret
-> BatchDisassociateScramSecret -> Bool
$c/= :: BatchDisassociateScramSecret
-> BatchDisassociateScramSecret -> Bool
== :: BatchDisassociateScramSecret
-> BatchDisassociateScramSecret -> Bool
$c== :: BatchDisassociateScramSecret
-> BatchDisassociateScramSecret -> Bool
Prelude.Eq, ReadPrec [BatchDisassociateScramSecret]
ReadPrec BatchDisassociateScramSecret
Int -> ReadS BatchDisassociateScramSecret
ReadS [BatchDisassociateScramSecret]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDisassociateScramSecret]
$creadListPrec :: ReadPrec [BatchDisassociateScramSecret]
readPrec :: ReadPrec BatchDisassociateScramSecret
$creadPrec :: ReadPrec BatchDisassociateScramSecret
readList :: ReadS [BatchDisassociateScramSecret]
$creadList :: ReadS [BatchDisassociateScramSecret]
readsPrec :: Int -> ReadS BatchDisassociateScramSecret
$creadsPrec :: Int -> ReadS BatchDisassociateScramSecret
Prelude.Read, Int -> BatchDisassociateScramSecret -> ShowS
[BatchDisassociateScramSecret] -> ShowS
BatchDisassociateScramSecret -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDisassociateScramSecret] -> ShowS
$cshowList :: [BatchDisassociateScramSecret] -> ShowS
show :: BatchDisassociateScramSecret -> String
$cshow :: BatchDisassociateScramSecret -> String
showsPrec :: Int -> BatchDisassociateScramSecret -> ShowS
$cshowsPrec :: Int -> BatchDisassociateScramSecret -> ShowS
Prelude.Show, forall x.
Rep BatchDisassociateScramSecret x -> BatchDisassociateScramSecret
forall x.
BatchDisassociateScramSecret -> Rep BatchDisassociateScramSecret x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDisassociateScramSecret x -> BatchDisassociateScramSecret
$cfrom :: forall x.
BatchDisassociateScramSecret -> Rep BatchDisassociateScramSecret x
Prelude.Generic)

-- |
-- Create a value of 'BatchDisassociateScramSecret' 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:
--
-- 'clusterArn', 'batchDisassociateScramSecret_clusterArn' - The Amazon Resource Name (ARN) of the cluster to be updated.
--
-- 'secretArnList', 'batchDisassociateScramSecret_secretArnList' - List of AWS Secrets Manager secret ARNs.
newBatchDisassociateScramSecret ::
  -- | 'clusterArn'
  Prelude.Text ->
  BatchDisassociateScramSecret
newBatchDisassociateScramSecret :: Text -> BatchDisassociateScramSecret
newBatchDisassociateScramSecret Text
pClusterArn_ =
  BatchDisassociateScramSecret'
    { $sel:clusterArn:BatchDisassociateScramSecret' :: Text
clusterArn =
        Text
pClusterArn_,
      $sel:secretArnList:BatchDisassociateScramSecret' :: [Text]
secretArnList = forall a. Monoid a => a
Prelude.mempty
    }

-- | The Amazon Resource Name (ARN) of the cluster to be updated.
batchDisassociateScramSecret_clusterArn :: Lens.Lens' BatchDisassociateScramSecret Prelude.Text
batchDisassociateScramSecret_clusterArn :: Lens' BatchDisassociateScramSecret Text
batchDisassociateScramSecret_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDisassociateScramSecret' {Text
clusterArn :: Text
$sel:clusterArn:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> Text
clusterArn} -> Text
clusterArn) (\s :: BatchDisassociateScramSecret
s@BatchDisassociateScramSecret' {} Text
a -> BatchDisassociateScramSecret
s {$sel:clusterArn:BatchDisassociateScramSecret' :: Text
clusterArn = Text
a} :: BatchDisassociateScramSecret)

-- | List of AWS Secrets Manager secret ARNs.
batchDisassociateScramSecret_secretArnList :: Lens.Lens' BatchDisassociateScramSecret [Prelude.Text]
batchDisassociateScramSecret_secretArnList :: Lens' BatchDisassociateScramSecret [Text]
batchDisassociateScramSecret_secretArnList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDisassociateScramSecret' {[Text]
secretArnList :: [Text]
$sel:secretArnList:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> [Text]
secretArnList} -> [Text]
secretArnList) (\s :: BatchDisassociateScramSecret
s@BatchDisassociateScramSecret' {} [Text]
a -> BatchDisassociateScramSecret
s {$sel:secretArnList:BatchDisassociateScramSecret' :: [Text]
secretArnList = [Text]
a} :: BatchDisassociateScramSecret) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchDisassociateScramSecret where
  type
    AWSResponse BatchDisassociateScramSecret =
      BatchDisassociateScramSecretResponse
  request :: (Service -> Service)
-> BatchDisassociateScramSecret
-> Request BatchDisassociateScramSecret
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy BatchDisassociateScramSecret
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchDisassociateScramSecret)))
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 [UnprocessedScramSecret]
-> Int
-> BatchDisassociateScramSecretResponse
BatchDisassociateScramSecretResponse'
            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
"clusterArn")
            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
"unprocessedScramSecrets"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
    BatchDisassociateScramSecret
  where
  hashWithSalt :: Int -> BatchDisassociateScramSecret -> Int
hashWithSalt Int
_salt BatchDisassociateScramSecret' {[Text]
Text
secretArnList :: [Text]
clusterArn :: Text
$sel:secretArnList:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> [Text]
$sel:clusterArn:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
secretArnList

instance Prelude.NFData BatchDisassociateScramSecret where
  rnf :: BatchDisassociateScramSecret -> ()
rnf BatchDisassociateScramSecret' {[Text]
Text
secretArnList :: [Text]
clusterArn :: Text
$sel:secretArnList:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> [Text]
$sel:clusterArn:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
secretArnList

instance Data.ToHeaders BatchDisassociateScramSecret where
  toHeaders :: BatchDisassociateScramSecret -> 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 BatchDisassociateScramSecret where
  toJSON :: BatchDisassociateScramSecret -> Value
toJSON BatchDisassociateScramSecret' {[Text]
Text
secretArnList :: [Text]
clusterArn :: Text
$sel:secretArnList:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> [Text]
$sel:clusterArn:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"secretArnList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
secretArnList)
          ]
      )

instance Data.ToPath BatchDisassociateScramSecret where
  toPath :: BatchDisassociateScramSecret -> ByteString
toPath BatchDisassociateScramSecret' {[Text]
Text
secretArnList :: [Text]
clusterArn :: Text
$sel:secretArnList:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> [Text]
$sel:clusterArn:BatchDisassociateScramSecret' :: BatchDisassociateScramSecret -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/clusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn,
        ByteString
"/scram-secrets"
      ]

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

-- | /See:/ 'newBatchDisassociateScramSecretResponse' smart constructor.
data BatchDisassociateScramSecretResponse = BatchDisassociateScramSecretResponse'
  { -- | The Amazon Resource Name (ARN) of the cluster.
    BatchDisassociateScramSecretResponse -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | List of errors when disassociating secrets to cluster.
    BatchDisassociateScramSecretResponse
-> Maybe [UnprocessedScramSecret]
unprocessedScramSecrets :: Prelude.Maybe [UnprocessedScramSecret],
    -- | The response's http status code.
    BatchDisassociateScramSecretResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchDisassociateScramSecretResponse
-> BatchDisassociateScramSecretResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDisassociateScramSecretResponse
-> BatchDisassociateScramSecretResponse -> Bool
$c/= :: BatchDisassociateScramSecretResponse
-> BatchDisassociateScramSecretResponse -> Bool
== :: BatchDisassociateScramSecretResponse
-> BatchDisassociateScramSecretResponse -> Bool
$c== :: BatchDisassociateScramSecretResponse
-> BatchDisassociateScramSecretResponse -> Bool
Prelude.Eq, ReadPrec [BatchDisassociateScramSecretResponse]
ReadPrec BatchDisassociateScramSecretResponse
Int -> ReadS BatchDisassociateScramSecretResponse
ReadS [BatchDisassociateScramSecretResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDisassociateScramSecretResponse]
$creadListPrec :: ReadPrec [BatchDisassociateScramSecretResponse]
readPrec :: ReadPrec BatchDisassociateScramSecretResponse
$creadPrec :: ReadPrec BatchDisassociateScramSecretResponse
readList :: ReadS [BatchDisassociateScramSecretResponse]
$creadList :: ReadS [BatchDisassociateScramSecretResponse]
readsPrec :: Int -> ReadS BatchDisassociateScramSecretResponse
$creadsPrec :: Int -> ReadS BatchDisassociateScramSecretResponse
Prelude.Read, Int -> BatchDisassociateScramSecretResponse -> ShowS
[BatchDisassociateScramSecretResponse] -> ShowS
BatchDisassociateScramSecretResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDisassociateScramSecretResponse] -> ShowS
$cshowList :: [BatchDisassociateScramSecretResponse] -> ShowS
show :: BatchDisassociateScramSecretResponse -> String
$cshow :: BatchDisassociateScramSecretResponse -> String
showsPrec :: Int -> BatchDisassociateScramSecretResponse -> ShowS
$cshowsPrec :: Int -> BatchDisassociateScramSecretResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDisassociateScramSecretResponse x
-> BatchDisassociateScramSecretResponse
forall x.
BatchDisassociateScramSecretResponse
-> Rep BatchDisassociateScramSecretResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDisassociateScramSecretResponse x
-> BatchDisassociateScramSecretResponse
$cfrom :: forall x.
BatchDisassociateScramSecretResponse
-> Rep BatchDisassociateScramSecretResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchDisassociateScramSecretResponse' 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:
--
-- 'clusterArn', 'batchDisassociateScramSecretResponse_clusterArn' - The Amazon Resource Name (ARN) of the cluster.
--
-- 'unprocessedScramSecrets', 'batchDisassociateScramSecretResponse_unprocessedScramSecrets' - List of errors when disassociating secrets to cluster.
--
-- 'httpStatus', 'batchDisassociateScramSecretResponse_httpStatus' - The response's http status code.
newBatchDisassociateScramSecretResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchDisassociateScramSecretResponse
newBatchDisassociateScramSecretResponse :: Int -> BatchDisassociateScramSecretResponse
newBatchDisassociateScramSecretResponse Int
pHttpStatus_ =
  BatchDisassociateScramSecretResponse'
    { $sel:clusterArn:BatchDisassociateScramSecretResponse' :: Maybe Text
clusterArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:unprocessedScramSecrets:BatchDisassociateScramSecretResponse' :: Maybe [UnprocessedScramSecret]
unprocessedScramSecrets =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchDisassociateScramSecretResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the cluster.
batchDisassociateScramSecretResponse_clusterArn :: Lens.Lens' BatchDisassociateScramSecretResponse (Prelude.Maybe Prelude.Text)
batchDisassociateScramSecretResponse_clusterArn :: Lens' BatchDisassociateScramSecretResponse (Maybe Text)
batchDisassociateScramSecretResponse_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDisassociateScramSecretResponse' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: BatchDisassociateScramSecretResponse
s@BatchDisassociateScramSecretResponse' {} Maybe Text
a -> BatchDisassociateScramSecretResponse
s {$sel:clusterArn:BatchDisassociateScramSecretResponse' :: Maybe Text
clusterArn = Maybe Text
a} :: BatchDisassociateScramSecretResponse)

-- | List of errors when disassociating secrets to cluster.
batchDisassociateScramSecretResponse_unprocessedScramSecrets :: Lens.Lens' BatchDisassociateScramSecretResponse (Prelude.Maybe [UnprocessedScramSecret])
batchDisassociateScramSecretResponse_unprocessedScramSecrets :: Lens'
  BatchDisassociateScramSecretResponse
  (Maybe [UnprocessedScramSecret])
batchDisassociateScramSecretResponse_unprocessedScramSecrets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDisassociateScramSecretResponse' {Maybe [UnprocessedScramSecret]
unprocessedScramSecrets :: Maybe [UnprocessedScramSecret]
$sel:unprocessedScramSecrets:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse
-> Maybe [UnprocessedScramSecret]
unprocessedScramSecrets} -> Maybe [UnprocessedScramSecret]
unprocessedScramSecrets) (\s :: BatchDisassociateScramSecretResponse
s@BatchDisassociateScramSecretResponse' {} Maybe [UnprocessedScramSecret]
a -> BatchDisassociateScramSecretResponse
s {$sel:unprocessedScramSecrets:BatchDisassociateScramSecretResponse' :: Maybe [UnprocessedScramSecret]
unprocessedScramSecrets = Maybe [UnprocessedScramSecret]
a} :: BatchDisassociateScramSecretResponse) 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 response's http status code.
batchDisassociateScramSecretResponse_httpStatus :: Lens.Lens' BatchDisassociateScramSecretResponse Prelude.Int
batchDisassociateScramSecretResponse_httpStatus :: Lens' BatchDisassociateScramSecretResponse Int
batchDisassociateScramSecretResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDisassociateScramSecretResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchDisassociateScramSecretResponse
s@BatchDisassociateScramSecretResponse' {} Int
a -> BatchDisassociateScramSecretResponse
s {$sel:httpStatus:BatchDisassociateScramSecretResponse' :: Int
httpStatus = Int
a} :: BatchDisassociateScramSecretResponse)

instance
  Prelude.NFData
    BatchDisassociateScramSecretResponse
  where
  rnf :: BatchDisassociateScramSecretResponse -> ()
rnf BatchDisassociateScramSecretResponse' {Int
Maybe [UnprocessedScramSecret]
Maybe Text
httpStatus :: Int
unprocessedScramSecrets :: Maybe [UnprocessedScramSecret]
clusterArn :: Maybe Text
$sel:httpStatus:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse -> Int
$sel:unprocessedScramSecrets:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse
-> Maybe [UnprocessedScramSecret]
$sel:clusterArn:BatchDisassociateScramSecretResponse' :: BatchDisassociateScramSecretResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [UnprocessedScramSecret]
unprocessedScramSecrets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus