{-# 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 #-}
module Amazonka.DynamoDB.BatchExecuteStatement
(
BatchExecuteStatement (..),
newBatchExecuteStatement,
batchExecuteStatement_returnConsumedCapacity,
batchExecuteStatement_statements,
BatchExecuteStatementResponse (..),
newBatchExecuteStatementResponse,
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
data BatchExecuteStatement = BatchExecuteStatement'
{ BatchExecuteStatement -> Maybe ReturnConsumedCapacity
returnConsumedCapacity :: Prelude.Maybe ReturnConsumedCapacity,
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)
newBatchExecuteStatement ::
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_
}
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)
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
data BatchExecuteStatementResponse = BatchExecuteStatementResponse'
{
BatchExecuteStatementResponse -> Maybe [ConsumedCapacity]
consumedCapacity :: Prelude.Maybe [ConsumedCapacity],
BatchExecuteStatementResponse -> Maybe [BatchStatementResponse]
responses :: Prelude.Maybe [BatchStatementResponse],
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)
newBatchExecuteStatementResponse ::
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_
}
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
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
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