{-# 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.DynamoDB.BatchExecuteStatement
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation allows you to perform batch reads or writes on data
-- stored in DynamoDB, using PartiQL. Each read statement in a
-- @BatchExecuteStatement@ must specify an equality condition on all key
-- attributes. This enforces that each @SELECT@ statement in a batch
-- returns at most a single item.
--
-- The entire batch must consist of either read statements or write
-- statements, you cannot mix both in one batch.
--
-- A HTTP 200 response does not mean that all statements in the
-- BatchExecuteStatement succeeded. Error details for individual statements
-- can be found under the
-- <https://docs.aws.amazon.com/amazondynamodb/latest/APIReference/API_BatchStatementResponse.html#DDB-Type-BatchStatementResponse-Error Error>
-- field of the @BatchStatementResponse@ for each statement.
module Amazonka.DynamoDB.BatchExecuteStatement
  ( -- * Creating a Request
    BatchExecuteStatement (..),
    newBatchExecuteStatement,

    -- * Request Lenses
    batchExecuteStatement_returnConsumedCapacity,
    batchExecuteStatement_statements,

    -- * Destructuring the Response
    BatchExecuteStatementResponse (..),
    newBatchExecuteStatementResponse,

    -- * Response Lenses
    batchExecuteStatementResponse_consumedCapacity,
    batchExecuteStatementResponse_responses,
    batchExecuteStatementResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchExecuteStatement' smart constructor.
data BatchExecuteStatement = BatchExecuteStatement'
  { BatchExecuteStatement -> Maybe ReturnConsumedCapacity
returnConsumedCapacity :: Prelude.Maybe ReturnConsumedCapacity,
    -- | The list of PartiQL statements representing the batch to run.
    BatchExecuteStatement -> NonEmpty BatchStatementRequest
statements :: Prelude.NonEmpty BatchStatementRequest
  }
  deriving (BatchExecuteStatement -> BatchExecuteStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchExecuteStatement -> BatchExecuteStatement -> Bool
$c/= :: BatchExecuteStatement -> BatchExecuteStatement -> Bool
== :: BatchExecuteStatement -> BatchExecuteStatement -> Bool
$c== :: BatchExecuteStatement -> BatchExecuteStatement -> Bool
Prelude.Eq, ReadPrec [BatchExecuteStatement]
ReadPrec BatchExecuteStatement
Int -> ReadS BatchExecuteStatement
ReadS [BatchExecuteStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchExecuteStatement]
$creadListPrec :: ReadPrec [BatchExecuteStatement]
readPrec :: ReadPrec BatchExecuteStatement
$creadPrec :: ReadPrec BatchExecuteStatement
readList :: ReadS [BatchExecuteStatement]
$creadList :: ReadS [BatchExecuteStatement]
readsPrec :: Int -> ReadS BatchExecuteStatement
$creadsPrec :: Int -> ReadS BatchExecuteStatement
Prelude.Read, Int -> BatchExecuteStatement -> ShowS
[BatchExecuteStatement] -> ShowS
BatchExecuteStatement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchExecuteStatement] -> ShowS
$cshowList :: [BatchExecuteStatement] -> ShowS
show :: BatchExecuteStatement -> String
$cshow :: BatchExecuteStatement -> String
showsPrec :: Int -> BatchExecuteStatement -> ShowS
$cshowsPrec :: Int -> BatchExecuteStatement -> ShowS
Prelude.Show, forall x. Rep BatchExecuteStatement x -> BatchExecuteStatement
forall x. BatchExecuteStatement -> Rep BatchExecuteStatement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchExecuteStatement x -> BatchExecuteStatement
$cfrom :: forall x. BatchExecuteStatement -> Rep BatchExecuteStatement x
Prelude.Generic)

-- |
-- Create a value of 'BatchExecuteStatement' 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:
--
-- 'returnConsumedCapacity', 'batchExecuteStatement_returnConsumedCapacity' - Undocumented member.
--
-- 'statements', 'batchExecuteStatement_statements' - The list of PartiQL statements representing the batch to run.
newBatchExecuteStatement ::
  -- | 'statements'
  Prelude.NonEmpty BatchStatementRequest ->
  BatchExecuteStatement
newBatchExecuteStatement :: NonEmpty BatchStatementRequest -> BatchExecuteStatement
newBatchExecuteStatement NonEmpty BatchStatementRequest
pStatements_ =
  BatchExecuteStatement'
    { $sel:returnConsumedCapacity:BatchExecuteStatement' :: Maybe ReturnConsumedCapacity
returnConsumedCapacity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:statements:BatchExecuteStatement' :: NonEmpty BatchStatementRequest
statements = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty BatchStatementRequest
pStatements_
    }

-- | Undocumented member.
batchExecuteStatement_returnConsumedCapacity :: Lens.Lens' BatchExecuteStatement (Prelude.Maybe ReturnConsumedCapacity)
batchExecuteStatement_returnConsumedCapacity :: Lens' BatchExecuteStatement (Maybe ReturnConsumedCapacity)
batchExecuteStatement_returnConsumedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchExecuteStatement' {Maybe ReturnConsumedCapacity
returnConsumedCapacity :: Maybe ReturnConsumedCapacity
$sel:returnConsumedCapacity:BatchExecuteStatement' :: BatchExecuteStatement -> Maybe ReturnConsumedCapacity
returnConsumedCapacity} -> Maybe ReturnConsumedCapacity
returnConsumedCapacity) (\s :: BatchExecuteStatement
s@BatchExecuteStatement' {} Maybe ReturnConsumedCapacity
a -> BatchExecuteStatement
s {$sel:returnConsumedCapacity:BatchExecuteStatement' :: Maybe ReturnConsumedCapacity
returnConsumedCapacity = Maybe ReturnConsumedCapacity
a} :: BatchExecuteStatement)

-- | The list of PartiQL statements representing the batch to run.
batchExecuteStatement_statements :: Lens.Lens' BatchExecuteStatement (Prelude.NonEmpty BatchStatementRequest)
batchExecuteStatement_statements :: Lens' BatchExecuteStatement (NonEmpty BatchStatementRequest)
batchExecuteStatement_statements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchExecuteStatement' {NonEmpty BatchStatementRequest
statements :: NonEmpty BatchStatementRequest
$sel:statements:BatchExecuteStatement' :: BatchExecuteStatement -> NonEmpty BatchStatementRequest
statements} -> NonEmpty BatchStatementRequest
statements) (\s :: BatchExecuteStatement
s@BatchExecuteStatement' {} NonEmpty BatchStatementRequest
a -> BatchExecuteStatement
s {$sel:statements:BatchExecuteStatement' :: NonEmpty BatchStatementRequest
statements = NonEmpty BatchStatementRequest
a} :: BatchExecuteStatement) 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 BatchExecuteStatement where
  type
    AWSResponse BatchExecuteStatement =
      BatchExecuteStatementResponse
  request :: (Service -> Service)
-> BatchExecuteStatement -> Request BatchExecuteStatement
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 BatchExecuteStatement
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchExecuteStatement)))
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 [ConsumedCapacity]
-> Maybe [BatchStatementResponse]
-> Int
-> BatchExecuteStatementResponse
BatchExecuteStatementResponse'
            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
"ConsumedCapacity"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Responses" 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 BatchExecuteStatement where
  hashWithSalt :: Int -> BatchExecuteStatement -> Int
hashWithSalt Int
_salt BatchExecuteStatement' {Maybe ReturnConsumedCapacity
NonEmpty BatchStatementRequest
statements :: NonEmpty BatchStatementRequest
returnConsumedCapacity :: Maybe ReturnConsumedCapacity
$sel:statements:BatchExecuteStatement' :: BatchExecuteStatement -> NonEmpty BatchStatementRequest
$sel:returnConsumedCapacity:BatchExecuteStatement' :: BatchExecuteStatement -> Maybe ReturnConsumedCapacity
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReturnConsumedCapacity
returnConsumedCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty BatchStatementRequest
statements

instance Prelude.NFData BatchExecuteStatement where
  rnf :: BatchExecuteStatement -> ()
rnf BatchExecuteStatement' {Maybe ReturnConsumedCapacity
NonEmpty BatchStatementRequest
statements :: NonEmpty BatchStatementRequest
returnConsumedCapacity :: Maybe ReturnConsumedCapacity
$sel:statements:BatchExecuteStatement' :: BatchExecuteStatement -> NonEmpty BatchStatementRequest
$sel:returnConsumedCapacity:BatchExecuteStatement' :: BatchExecuteStatement -> Maybe ReturnConsumedCapacity
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ReturnConsumedCapacity
returnConsumedCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty BatchStatementRequest
statements

instance Data.ToHeaders BatchExecuteStatement where
  toHeaders :: BatchExecuteStatement -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"DynamoDB_20120810.BatchExecuteStatement" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON BatchExecuteStatement where
  toJSON :: BatchExecuteStatement -> Value
toJSON BatchExecuteStatement' {Maybe ReturnConsumedCapacity
NonEmpty BatchStatementRequest
statements :: NonEmpty BatchStatementRequest
returnConsumedCapacity :: Maybe ReturnConsumedCapacity
$sel:statements:BatchExecuteStatement' :: BatchExecuteStatement -> NonEmpty BatchStatementRequest
$sel:returnConsumedCapacity:BatchExecuteStatement' :: BatchExecuteStatement -> Maybe ReturnConsumedCapacity
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ReturnConsumedCapacity" 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 ReturnConsumedCapacity
returnConsumedCapacity,
            forall a. a -> Maybe a
Prelude.Just (Key
"Statements" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty BatchStatementRequest
statements)
          ]
      )

instance Data.ToPath BatchExecuteStatement where
  toPath :: BatchExecuteStatement -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newBatchExecuteStatementResponse' smart constructor.
data BatchExecuteStatementResponse = BatchExecuteStatementResponse'
  { -- | The capacity units consumed by the entire operation. The values of the
    -- list are ordered according to the ordering of the statements.
    BatchExecuteStatementResponse -> Maybe [ConsumedCapacity]
consumedCapacity :: Prelude.Maybe [ConsumedCapacity],
    -- | The response to each PartiQL statement in the batch.
    BatchExecuteStatementResponse -> Maybe [BatchStatementResponse]
responses :: Prelude.Maybe [BatchStatementResponse],
    -- | The response's http status code.
    BatchExecuteStatementResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchExecuteStatementResponse
-> BatchExecuteStatementResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchExecuteStatementResponse
-> BatchExecuteStatementResponse -> Bool
$c/= :: BatchExecuteStatementResponse
-> BatchExecuteStatementResponse -> Bool
== :: BatchExecuteStatementResponse
-> BatchExecuteStatementResponse -> Bool
$c== :: BatchExecuteStatementResponse
-> BatchExecuteStatementResponse -> Bool
Prelude.Eq, ReadPrec [BatchExecuteStatementResponse]
ReadPrec BatchExecuteStatementResponse
Int -> ReadS BatchExecuteStatementResponse
ReadS [BatchExecuteStatementResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchExecuteStatementResponse]
$creadListPrec :: ReadPrec [BatchExecuteStatementResponse]
readPrec :: ReadPrec BatchExecuteStatementResponse
$creadPrec :: ReadPrec BatchExecuteStatementResponse
readList :: ReadS [BatchExecuteStatementResponse]
$creadList :: ReadS [BatchExecuteStatementResponse]
readsPrec :: Int -> ReadS BatchExecuteStatementResponse
$creadsPrec :: Int -> ReadS BatchExecuteStatementResponse
Prelude.Read, Int -> BatchExecuteStatementResponse -> ShowS
[BatchExecuteStatementResponse] -> ShowS
BatchExecuteStatementResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchExecuteStatementResponse] -> ShowS
$cshowList :: [BatchExecuteStatementResponse] -> ShowS
show :: BatchExecuteStatementResponse -> String
$cshow :: BatchExecuteStatementResponse -> String
showsPrec :: Int -> BatchExecuteStatementResponse -> ShowS
$cshowsPrec :: Int -> BatchExecuteStatementResponse -> ShowS
Prelude.Show, forall x.
Rep BatchExecuteStatementResponse x
-> BatchExecuteStatementResponse
forall x.
BatchExecuteStatementResponse
-> Rep BatchExecuteStatementResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchExecuteStatementResponse x
-> BatchExecuteStatementResponse
$cfrom :: forall x.
BatchExecuteStatementResponse
-> Rep BatchExecuteStatementResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchExecuteStatementResponse' 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:
--
-- 'consumedCapacity', 'batchExecuteStatementResponse_consumedCapacity' - The capacity units consumed by the entire operation. The values of the
-- list are ordered according to the ordering of the statements.
--
-- 'responses', 'batchExecuteStatementResponse_responses' - The response to each PartiQL statement in the batch.
--
-- 'httpStatus', 'batchExecuteStatementResponse_httpStatus' - The response's http status code.
newBatchExecuteStatementResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchExecuteStatementResponse
newBatchExecuteStatementResponse :: Int -> BatchExecuteStatementResponse
newBatchExecuteStatementResponse Int
pHttpStatus_ =
  BatchExecuteStatementResponse'
    { $sel:consumedCapacity:BatchExecuteStatementResponse' :: Maybe [ConsumedCapacity]
consumedCapacity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:responses:BatchExecuteStatementResponse' :: Maybe [BatchStatementResponse]
responses = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchExecuteStatementResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The capacity units consumed by the entire operation. The values of the
-- list are ordered according to the ordering of the statements.
batchExecuteStatementResponse_consumedCapacity :: Lens.Lens' BatchExecuteStatementResponse (Prelude.Maybe [ConsumedCapacity])
batchExecuteStatementResponse_consumedCapacity :: Lens' BatchExecuteStatementResponse (Maybe [ConsumedCapacity])
batchExecuteStatementResponse_consumedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchExecuteStatementResponse' {Maybe [ConsumedCapacity]
consumedCapacity :: Maybe [ConsumedCapacity]
$sel:consumedCapacity:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Maybe [ConsumedCapacity]
consumedCapacity} -> Maybe [ConsumedCapacity]
consumedCapacity) (\s :: BatchExecuteStatementResponse
s@BatchExecuteStatementResponse' {} Maybe [ConsumedCapacity]
a -> BatchExecuteStatementResponse
s {$sel:consumedCapacity:BatchExecuteStatementResponse' :: Maybe [ConsumedCapacity]
consumedCapacity = Maybe [ConsumedCapacity]
a} :: BatchExecuteStatementResponse) 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 to each PartiQL statement in the batch.
batchExecuteStatementResponse_responses :: Lens.Lens' BatchExecuteStatementResponse (Prelude.Maybe [BatchStatementResponse])
batchExecuteStatementResponse_responses :: Lens'
  BatchExecuteStatementResponse (Maybe [BatchStatementResponse])
batchExecuteStatementResponse_responses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchExecuteStatementResponse' {Maybe [BatchStatementResponse]
responses :: Maybe [BatchStatementResponse]
$sel:responses:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Maybe [BatchStatementResponse]
responses} -> Maybe [BatchStatementResponse]
responses) (\s :: BatchExecuteStatementResponse
s@BatchExecuteStatementResponse' {} Maybe [BatchStatementResponse]
a -> BatchExecuteStatementResponse
s {$sel:responses:BatchExecuteStatementResponse' :: Maybe [BatchStatementResponse]
responses = Maybe [BatchStatementResponse]
a} :: BatchExecuteStatementResponse) 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.
batchExecuteStatementResponse_httpStatus :: Lens.Lens' BatchExecuteStatementResponse Prelude.Int
batchExecuteStatementResponse_httpStatus :: Lens' BatchExecuteStatementResponse Int
batchExecuteStatementResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchExecuteStatementResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchExecuteStatementResponse
s@BatchExecuteStatementResponse' {} Int
a -> BatchExecuteStatementResponse
s {$sel:httpStatus:BatchExecuteStatementResponse' :: Int
httpStatus = Int
a} :: BatchExecuteStatementResponse)

instance Prelude.NFData BatchExecuteStatementResponse where
  rnf :: BatchExecuteStatementResponse -> ()
rnf BatchExecuteStatementResponse' {Int
Maybe [ConsumedCapacity]
Maybe [BatchStatementResponse]
httpStatus :: Int
responses :: Maybe [BatchStatementResponse]
consumedCapacity :: Maybe [ConsumedCapacity]
$sel:httpStatus:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Int
$sel:responses:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Maybe [BatchStatementResponse]
$sel:consumedCapacity:BatchExecuteStatementResponse' :: BatchExecuteStatementResponse -> Maybe [ConsumedCapacity]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConsumedCapacity]
consumedCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [BatchStatementResponse]
responses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus