module Aws.SimpleDb.Commands.Attributes where
import Aws.Core
import Aws.SimpleDb.Core
import Control.Applicative
import Control.Monad
import Data.Maybe
import Prelude
import Text.XML.Cursor (($//), (&|))
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Text.XML.Cursor as Cu
data GetAttributes
= GetAttributes {
GetAttributes -> Text
gaItemName :: T.Text
, GetAttributes -> Maybe Text
gaAttributeName :: Maybe T.Text
, GetAttributes -> Bool
gaConsistentRead :: Bool
, GetAttributes -> Text
gaDomainName :: T.Text
}
deriving (Int -> GetAttributes -> ShowS
[GetAttributes] -> ShowS
GetAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAttributes] -> ShowS
$cshowList :: [GetAttributes] -> ShowS
show :: GetAttributes -> String
$cshow :: GetAttributes -> String
showsPrec :: Int -> GetAttributes -> ShowS
$cshowsPrec :: Int -> GetAttributes -> ShowS
Show)
data GetAttributesResponse
= GetAttributesResponse {
GetAttributesResponse -> [Attribute Text]
garAttributes :: [Attribute T.Text]
}
deriving (Int -> GetAttributesResponse -> ShowS
[GetAttributesResponse] -> ShowS
GetAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAttributesResponse] -> ShowS
$cshowList :: [GetAttributesResponse] -> ShowS
show :: GetAttributesResponse -> String
$cshow :: GetAttributesResponse -> String
showsPrec :: Int -> GetAttributesResponse -> ShowS
$cshowsPrec :: Int -> GetAttributesResponse -> ShowS
Show)
getAttributes :: T.Text -> T.Text -> GetAttributes
getAttributes :: Text -> Text -> GetAttributes
getAttributes Text
item Text
domain = GetAttributes { gaItemName :: Text
gaItemName = Text
item, gaAttributeName :: Maybe Text
gaAttributeName = forall a. Maybe a
Nothing, gaConsistentRead :: Bool
gaConsistentRead = Bool
False, gaDomainName :: Text
gaDomainName = Text
domain }
instance SignQuery GetAttributes where
type ServiceConfiguration GetAttributes = SdbConfiguration
signQuery :: forall queryType.
GetAttributes
-> ServiceConfiguration GetAttributes queryType
-> SignatureData
-> SignedQuery
signQuery GetAttributes{Bool
Maybe Text
Text
gaDomainName :: Text
gaConsistentRead :: Bool
gaAttributeName :: Maybe Text
gaItemName :: Text
gaDomainName :: GetAttributes -> Text
gaConsistentRead :: GetAttributes -> Bool
gaAttributeName :: GetAttributes -> Maybe Text
gaItemName :: GetAttributes -> Text
..}
= forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery forall a b. (a -> b) -> a -> b
$
[(ByteString
"Action", ByteString
"GetAttributes"), (ByteString
"ItemName", Text -> ByteString
T.encodeUtf8 Text
gaItemName), (ByteString
"DomainName", Text -> ByteString
T.encodeUtf8 Text
gaDomainName)] forall a. [a] -> [a] -> [a]
++
forall a. Maybe a -> [a]
maybeToList ((ByteString
"AttributeName",) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ByteString
T.encodeUtf8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
gaAttributeName) forall a. [a] -> [a] -> [a]
++
(forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
gaConsistentRead forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [(ByteString
"ConsistentRead", ByteString
awsTrue)])
instance ResponseConsumer r GetAttributesResponse where
type ResponseMetadata GetAttributesResponse = SdbMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata GetAttributesResponse)
-> HTTPResponseConsumer GetAttributesResponse
responseConsumer Request
_ r
_
= forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer forall {m :: * -> *}.
MonadThrow m =>
Cursor -> m GetAttributesResponse
parse
where parse :: Cursor -> m GetAttributesResponse
parse Cursor
cursor = do
forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType () Text
"GetAttributesResponse" Cursor
cursor
[Attribute Text]
attributes <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence forall a b. (a -> b) -> a -> b
$ Cursor
cursor forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Axis
Cu.laxElement Text
"Attribute" forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| forall (m :: * -> *). MonadThrow m => Cursor -> m (Attribute Text)
readAttribute
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Attribute Text] -> GetAttributesResponse
GetAttributesResponse [Attribute Text]
attributes
instance Transaction GetAttributes GetAttributesResponse
instance AsMemoryResponse GetAttributesResponse where
type MemoryResponse GetAttributesResponse = GetAttributesResponse
loadToMemory :: GetAttributesResponse
-> ResourceT IO (MemoryResponse GetAttributesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return
data PutAttributes
= PutAttributes {
PutAttributes -> Text
paItemName :: T.Text
, PutAttributes -> [Attribute SetAttribute]
paAttributes :: [Attribute SetAttribute]
, PutAttributes -> [Attribute ExpectedAttribute]
paExpected :: [Attribute ExpectedAttribute]
, PutAttributes -> Text
paDomainName :: T.Text
}
deriving (Int -> PutAttributes -> ShowS
[PutAttributes] -> ShowS
PutAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutAttributes] -> ShowS
$cshowList :: [PutAttributes] -> ShowS
show :: PutAttributes -> String
$cshow :: PutAttributes -> String
showsPrec :: Int -> PutAttributes -> ShowS
$cshowsPrec :: Int -> PutAttributes -> ShowS
Show)
data PutAttributesResponse
= PutAttributesResponse
deriving (Int -> PutAttributesResponse -> ShowS
[PutAttributesResponse] -> ShowS
PutAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutAttributesResponse] -> ShowS
$cshowList :: [PutAttributesResponse] -> ShowS
show :: PutAttributesResponse -> String
$cshow :: PutAttributesResponse -> String
showsPrec :: Int -> PutAttributesResponse -> ShowS
$cshowsPrec :: Int -> PutAttributesResponse -> ShowS
Show)
putAttributes :: T.Text -> [Attribute SetAttribute] -> T.Text -> PutAttributes
putAttributes :: Text -> [Attribute SetAttribute] -> Text -> PutAttributes
putAttributes Text
item [Attribute SetAttribute]
attributes Text
domain = PutAttributes {
paItemName :: Text
paItemName = Text
item
, paAttributes :: [Attribute SetAttribute]
paAttributes = [Attribute SetAttribute]
attributes
, paExpected :: [Attribute ExpectedAttribute]
paExpected = []
, paDomainName :: Text
paDomainName = Text
domain
}
instance SignQuery PutAttributes where
type ServiceConfiguration PutAttributes = SdbConfiguration
signQuery :: forall queryType.
PutAttributes
-> ServiceConfiguration PutAttributes queryType
-> SignatureData
-> SignedQuery
signQuery PutAttributes{[Attribute ExpectedAttribute]
[Attribute SetAttribute]
Text
paDomainName :: Text
paExpected :: [Attribute ExpectedAttribute]
paAttributes :: [Attribute SetAttribute]
paItemName :: Text
paDomainName :: PutAttributes -> Text
paExpected :: PutAttributes -> [Attribute ExpectedAttribute]
paAttributes :: PutAttributes -> [Attribute SetAttribute]
paItemName :: PutAttributes -> Text
..}
= forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery forall a b. (a -> b) -> a -> b
$
[(ByteString
"Action", ByteString
"PutAttributes"), (ByteString
"ItemName", Text -> ByteString
T.encodeUtf8 Text
paItemName), (ByteString
"DomainName", Text -> ByteString
T.encodeUtf8 Text
paDomainName)] forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery SetAttribute -> [(ByteString, ByteString)]
setAttributeQuery) ByteString
"Attribute" [Attribute SetAttribute]
paAttributes forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery ExpectedAttribute -> [(ByteString, ByteString)]
expectedAttributeQuery) ByteString
"Expected" [Attribute ExpectedAttribute]
paExpected
instance ResponseConsumer r PutAttributesResponse where
type ResponseMetadata PutAttributesResponse = SdbMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata PutAttributesResponse)
-> HTTPResponseConsumer PutAttributesResponse
responseConsumer Request
_ r
_
= forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType PutAttributesResponse
PutAttributesResponse Text
"PutAttributesResponse"
instance Transaction PutAttributes PutAttributesResponse
instance AsMemoryResponse PutAttributesResponse where
type MemoryResponse PutAttributesResponse = PutAttributesResponse
loadToMemory :: PutAttributesResponse
-> ResourceT IO (MemoryResponse PutAttributesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return
data DeleteAttributes
= DeleteAttributes {
DeleteAttributes -> Text
daItemName :: T.Text
, DeleteAttributes -> [Attribute DeleteAttribute]
daAttributes :: [Attribute DeleteAttribute]
, DeleteAttributes -> [Attribute ExpectedAttribute]
daExpected :: [Attribute ExpectedAttribute]
, DeleteAttributes -> Text
daDomainName :: T.Text
}
deriving (Int -> DeleteAttributes -> ShowS
[DeleteAttributes] -> ShowS
DeleteAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAttributes] -> ShowS
$cshowList :: [DeleteAttributes] -> ShowS
show :: DeleteAttributes -> String
$cshow :: DeleteAttributes -> String
showsPrec :: Int -> DeleteAttributes -> ShowS
$cshowsPrec :: Int -> DeleteAttributes -> ShowS
Show)
data DeleteAttributesResponse
= DeleteAttributesResponse
deriving (Int -> DeleteAttributesResponse -> ShowS
[DeleteAttributesResponse] -> ShowS
DeleteAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAttributesResponse] -> ShowS
$cshowList :: [DeleteAttributesResponse] -> ShowS
show :: DeleteAttributesResponse -> String
$cshow :: DeleteAttributesResponse -> String
showsPrec :: Int -> DeleteAttributesResponse -> ShowS
$cshowsPrec :: Int -> DeleteAttributesResponse -> ShowS
Show)
deleteAttributes :: T.Text -> [Attribute DeleteAttribute] -> T.Text -> DeleteAttributes
deleteAttributes :: Text -> [Attribute DeleteAttribute] -> Text -> DeleteAttributes
deleteAttributes Text
item [Attribute DeleteAttribute]
attributes Text
domain = DeleteAttributes {
daItemName :: Text
daItemName = Text
item
, daAttributes :: [Attribute DeleteAttribute]
daAttributes = [Attribute DeleteAttribute]
attributes
, daExpected :: [Attribute ExpectedAttribute]
daExpected = []
, daDomainName :: Text
daDomainName = Text
domain
}
instance SignQuery DeleteAttributes where
type ServiceConfiguration DeleteAttributes = SdbConfiguration
signQuery :: forall queryType.
DeleteAttributes
-> ServiceConfiguration DeleteAttributes queryType
-> SignatureData
-> SignedQuery
signQuery DeleteAttributes{[Attribute ExpectedAttribute]
[Attribute DeleteAttribute]
Text
daDomainName :: Text
daExpected :: [Attribute ExpectedAttribute]
daAttributes :: [Attribute DeleteAttribute]
daItemName :: Text
daDomainName :: DeleteAttributes -> Text
daExpected :: DeleteAttributes -> [Attribute ExpectedAttribute]
daAttributes :: DeleteAttributes -> [Attribute DeleteAttribute]
daItemName :: DeleteAttributes -> Text
..}
= forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery forall a b. (a -> b) -> a -> b
$
[(ByteString
"Action", ByteString
"DeleteAttributes"), (ByteString
"ItemName", Text -> ByteString
T.encodeUtf8 Text
daItemName), (ByteString
"DomainName", Text -> ByteString
T.encodeUtf8 Text
daDomainName)] forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery DeleteAttribute -> [(ByteString, ByteString)]
deleteAttributeQuery) ByteString
"Attribute" [Attribute DeleteAttribute]
daAttributes forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery ExpectedAttribute -> [(ByteString, ByteString)]
expectedAttributeQuery) ByteString
"Expected" [Attribute ExpectedAttribute]
daExpected
instance ResponseConsumer r DeleteAttributesResponse where
type ResponseMetadata DeleteAttributesResponse = SdbMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata DeleteAttributesResponse)
-> HTTPResponseConsumer DeleteAttributesResponse
responseConsumer Request
_ r
_
= forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType DeleteAttributesResponse
DeleteAttributesResponse Text
"DeleteAttributesResponse"
instance Transaction DeleteAttributes DeleteAttributesResponse
instance AsMemoryResponse DeleteAttributesResponse where
type MemoryResponse DeleteAttributesResponse = DeleteAttributesResponse
loadToMemory :: DeleteAttributesResponse
-> ResourceT IO (MemoryResponse DeleteAttributesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return
data BatchPutAttributes
= BatchPutAttributes {
BatchPutAttributes -> [Item [Attribute SetAttribute]]
bpaItems :: [Item [Attribute SetAttribute]]
, BatchPutAttributes -> Text
bpaDomainName :: T.Text
}
deriving (Int -> BatchPutAttributes -> ShowS
[BatchPutAttributes] -> ShowS
BatchPutAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchPutAttributes] -> ShowS
$cshowList :: [BatchPutAttributes] -> ShowS
show :: BatchPutAttributes -> String
$cshow :: BatchPutAttributes -> String
showsPrec :: Int -> BatchPutAttributes -> ShowS
$cshowsPrec :: Int -> BatchPutAttributes -> ShowS
Show)
data BatchPutAttributesResponse
= BatchPutAttributesResponse
deriving (Int -> BatchPutAttributesResponse -> ShowS
[BatchPutAttributesResponse] -> ShowS
BatchPutAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchPutAttributesResponse] -> ShowS
$cshowList :: [BatchPutAttributesResponse] -> ShowS
show :: BatchPutAttributesResponse -> String
$cshow :: BatchPutAttributesResponse -> String
showsPrec :: Int -> BatchPutAttributesResponse -> ShowS
$cshowsPrec :: Int -> BatchPutAttributesResponse -> ShowS
Show)
batchPutAttributes :: [Item [Attribute SetAttribute]] -> T.Text -> BatchPutAttributes
batchPutAttributes :: [Item [Attribute SetAttribute]] -> Text -> BatchPutAttributes
batchPutAttributes [Item [Attribute SetAttribute]]
items Text
domain = BatchPutAttributes { bpaItems :: [Item [Attribute SetAttribute]]
bpaItems = [Item [Attribute SetAttribute]]
items, bpaDomainName :: Text
bpaDomainName = Text
domain }
instance SignQuery BatchPutAttributes where
type ServiceConfiguration BatchPutAttributes = SdbConfiguration
signQuery :: forall queryType.
BatchPutAttributes
-> ServiceConfiguration BatchPutAttributes queryType
-> SignatureData
-> SignedQuery
signQuery BatchPutAttributes{[Item [Attribute SetAttribute]]
Text
bpaDomainName :: Text
bpaItems :: [Item [Attribute SetAttribute]]
bpaDomainName :: BatchPutAttributes -> Text
bpaItems :: BatchPutAttributes -> [Item [Attribute SetAttribute]]
..}
= forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery forall a b. (a -> b) -> a -> b
$
[(ByteString
"Action", ByteString
"BatchPutAttributes")
, (ByteString
"DomainName", Text -> ByteString
T.encodeUtf8 Text
bpaDomainName)] forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Item a -> [(ByteString, ByteString)]
itemQuery forall a b. (a -> b) -> a -> b
$ forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery SetAttribute -> [(ByteString, ByteString)]
setAttributeQuery) ByteString
"Attribute") ByteString
"Item" [Item [Attribute SetAttribute]]
bpaItems
instance ResponseConsumer r BatchPutAttributesResponse where
type ResponseMetadata BatchPutAttributesResponse = SdbMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata BatchPutAttributesResponse)
-> HTTPResponseConsumer BatchPutAttributesResponse
responseConsumer Request
_ r
_
= forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType BatchPutAttributesResponse
BatchPutAttributesResponse Text
"BatchPutAttributesResponse"
instance Transaction BatchPutAttributes BatchPutAttributesResponse
instance AsMemoryResponse BatchPutAttributesResponse where
type MemoryResponse BatchPutAttributesResponse = BatchPutAttributesResponse
loadToMemory :: BatchPutAttributesResponse
-> ResourceT IO (MemoryResponse BatchPutAttributesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return
data BatchDeleteAttributes
= BatchDeleteAttributes {
BatchDeleteAttributes -> [Item [Attribute DeleteAttribute]]
bdaItems :: [Item [Attribute DeleteAttribute]]
, BatchDeleteAttributes -> Text
bdaDomainName :: T.Text
}
deriving (Int -> BatchDeleteAttributes -> ShowS
[BatchDeleteAttributes] -> ShowS
BatchDeleteAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteAttributes] -> ShowS
$cshowList :: [BatchDeleteAttributes] -> ShowS
show :: BatchDeleteAttributes -> String
$cshow :: BatchDeleteAttributes -> String
showsPrec :: Int -> BatchDeleteAttributes -> ShowS
$cshowsPrec :: Int -> BatchDeleteAttributes -> ShowS
Show)
data BatchDeleteAttributesResponse
= BatchDeleteAttributesResponse
deriving (Int -> BatchDeleteAttributesResponse -> ShowS
[BatchDeleteAttributesResponse] -> ShowS
BatchDeleteAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteAttributesResponse] -> ShowS
$cshowList :: [BatchDeleteAttributesResponse] -> ShowS
show :: BatchDeleteAttributesResponse -> String
$cshow :: BatchDeleteAttributesResponse -> String
showsPrec :: Int -> BatchDeleteAttributesResponse -> ShowS
$cshowsPrec :: Int -> BatchDeleteAttributesResponse -> ShowS
Show)
batchDeleteAttributes :: [Item [Attribute DeleteAttribute]] -> T.Text -> BatchDeleteAttributes
batchDeleteAttributes :: [Item [Attribute DeleteAttribute]] -> Text -> BatchDeleteAttributes
batchDeleteAttributes [Item [Attribute DeleteAttribute]]
items Text
domain = BatchDeleteAttributes { bdaItems :: [Item [Attribute DeleteAttribute]]
bdaItems = [Item [Attribute DeleteAttribute]]
items, bdaDomainName :: Text
bdaDomainName = Text
domain }
instance SignQuery BatchDeleteAttributes where
type ServiceConfiguration BatchDeleteAttributes = SdbConfiguration
signQuery :: forall queryType.
BatchDeleteAttributes
-> ServiceConfiguration BatchDeleteAttributes queryType
-> SignatureData
-> SignedQuery
signQuery BatchDeleteAttributes{[Item [Attribute DeleteAttribute]]
Text
bdaDomainName :: Text
bdaItems :: [Item [Attribute DeleteAttribute]]
bdaDomainName :: BatchDeleteAttributes -> Text
bdaItems :: BatchDeleteAttributes -> [Item [Attribute DeleteAttribute]]
..}
= forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery forall a b. (a -> b) -> a -> b
$
[(ByteString
"Action", ByteString
"BatchDeleteAttributes")
, (ByteString
"DomainName", Text -> ByteString
T.encodeUtf8 Text
bdaDomainName)] forall a. [a] -> [a] -> [a]
++
forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Item a -> [(ByteString, ByteString)]
itemQuery forall a b. (a -> b) -> a -> b
$ forall a.
(a -> [(ByteString, ByteString)])
-> ByteString -> [a] -> [(ByteString, ByteString)]
queryList (forall a.
(a -> [(ByteString, ByteString)])
-> Attribute a -> [(ByteString, ByteString)]
attributeQuery DeleteAttribute -> [(ByteString, ByteString)]
deleteAttributeQuery) ByteString
"Attribute") ByteString
"Item" [Item [Attribute DeleteAttribute]]
bdaItems
instance ResponseConsumer r BatchDeleteAttributesResponse where
type ResponseMetadata BatchDeleteAttributesResponse = SdbMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata BatchDeleteAttributesResponse)
-> HTTPResponseConsumer BatchDeleteAttributesResponse
responseConsumer Request
_ r
_
= forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType BatchDeleteAttributesResponse
BatchDeleteAttributesResponse Text
"BatchDeleteAttributesResponse"
instance Transaction BatchDeleteAttributes BatchDeleteAttributesResponse
instance AsMemoryResponse BatchDeleteAttributesResponse where
type MemoryResponse BatchDeleteAttributesResponse = BatchDeleteAttributesResponse
loadToMemory :: BatchDeleteAttributesResponse
-> ResourceT IO (MemoryResponse BatchDeleteAttributesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return