module Aws.Sqs.Commands.QueueAttributes where
import Aws.Core
import Aws.Sqs.Core
import Text.XML.Cursor (($/), ($//), (&/), (&|))
import qualified Data.ByteString.Char8 as B
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Text.XML.Cursor as Cu
data GetQueueAttributes = GetQueueAttributes {
GetQueueAttributes -> QueueName
gqaQueueName :: QueueName,
GetQueueAttributes -> [QueueAttribute]
gqaAttributes :: [QueueAttribute]
}deriving (Int -> GetQueueAttributes -> ShowS
[GetQueueAttributes] -> ShowS
GetQueueAttributes -> String
(Int -> GetQueueAttributes -> ShowS)
-> (GetQueueAttributes -> String)
-> ([GetQueueAttributes] -> ShowS)
-> Show GetQueueAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetQueueAttributes -> ShowS
showsPrec :: Int -> GetQueueAttributes -> ShowS
$cshow :: GetQueueAttributes -> String
show :: GetQueueAttributes -> String
$cshowList :: [GetQueueAttributes] -> ShowS
showList :: [GetQueueAttributes] -> ShowS
Show)
data GetQueueAttributesResponse = GetQueueAttributesResponse{
GetQueueAttributesResponse -> [(QueueAttribute, Text)]
gqarAttributes :: [(QueueAttribute,T.Text)]
} deriving (Int -> GetQueueAttributesResponse -> ShowS
[GetQueueAttributesResponse] -> ShowS
GetQueueAttributesResponse -> String
(Int -> GetQueueAttributesResponse -> ShowS)
-> (GetQueueAttributesResponse -> String)
-> ([GetQueueAttributesResponse] -> ShowS)
-> Show GetQueueAttributesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetQueueAttributesResponse -> ShowS
showsPrec :: Int -> GetQueueAttributesResponse -> ShowS
$cshow :: GetQueueAttributesResponse -> String
show :: GetQueueAttributesResponse -> String
$cshowList :: [GetQueueAttributesResponse] -> ShowS
showList :: [GetQueueAttributesResponse] -> ShowS
Show)
parseAttributes :: Cu.Cursor -> [(QueueAttribute, T.Text)]
parseAttributes :: Cursor -> [(QueueAttribute, Text)]
parseAttributes Cursor
el = do
Text
name <- String -> [Text] -> [Text]
forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force String
"Missing Name" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Cursor
el Cursor -> (Cursor -> [Text]) -> [Text]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Text -> Axis
Cu.laxElement Text
"Name" Axis -> (Cursor -> [Text]) -> Cursor -> [Text]
forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Cursor -> [Text]
Cu.content
Text
value <- String -> [Text] -> [Text]
forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force String
"Missing Value" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Cursor
el Cursor -> (Cursor -> [Text]) -> [Text]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Text -> Axis
Cu.laxElement Text
"Value" Axis -> (Cursor -> [Text]) -> Cursor -> [Text]
forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Cursor -> [Text]
Cu.content
QueueAttribute
parsedName <- Text -> [QueueAttribute]
forall (m :: * -> *). MonadThrow m => Text -> m QueueAttribute
parseQueueAttribute Text
name
(QueueAttribute, Text) -> [(QueueAttribute, Text)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (QueueAttribute
parsedName, Text
value)
instance ResponseConsumer r GetQueueAttributesResponse where
type ResponseMetadata GetQueueAttributesResponse = SqsMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata GetQueueAttributesResponse)
-> HTTPResponseConsumer GetQueueAttributesResponse
responseConsumer Request
_ r
_ = (Cursor -> Response SqsMetadata GetQueueAttributesResponse)
-> IORef SqsMetadata
-> HTTPResponseConsumer GetQueueAttributesResponse
forall a.
(Cursor -> Response SqsMetadata a)
-> IORef SqsMetadata -> HTTPResponseConsumer a
sqsXmlResponseConsumer Cursor -> Response SqsMetadata GetQueueAttributesResponse
forall {m :: * -> *}.
Monad m =>
Cursor -> m GetQueueAttributesResponse
parse
where
parse :: Cursor -> m GetQueueAttributesResponse
parse Cursor
el = do
let attributes :: [(QueueAttribute, Text)]
attributes = [[(QueueAttribute, Text)]] -> [(QueueAttribute, Text)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(QueueAttribute, Text)]] -> [(QueueAttribute, Text)])
-> [[(QueueAttribute, Text)]] -> [(QueueAttribute, Text)]
forall a b. (a -> b) -> a -> b
$ Cursor
el Cursor
-> (Cursor -> [[(QueueAttribute, Text)]])
-> [[(QueueAttribute, Text)]]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Axis
Cu.laxElement Text
"Attribute" Axis
-> (Cursor -> [(QueueAttribute, Text)])
-> Cursor
-> [[(QueueAttribute, Text)]]
forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| Cursor -> [(QueueAttribute, Text)]
parseAttributes
GetQueueAttributesResponse -> m GetQueueAttributesResponse
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return GetQueueAttributesResponse{ gqarAttributes :: [(QueueAttribute, Text)]
gqarAttributes = [(QueueAttribute, Text)]
attributes }
formatAttributes :: [QueueAttribute] -> [(B.ByteString, Maybe B.ByteString)]
formatAttributes :: [QueueAttribute] -> [(ByteString, Maybe ByteString)]
formatAttributes [QueueAttribute]
attrs =
case [QueueAttribute] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [QueueAttribute]
attrs of
Int
0 -> [(ByteString, Maybe ByteString)]
forall a. HasCallStack => a
undefined
Int
1 -> [(ByteString
"AttributeName", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
B.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ QueueAttribute -> Text
printQueueAttribute (QueueAttribute -> Text) -> QueueAttribute -> Text
forall a b. (a -> b) -> a -> b
$ [QueueAttribute]
attrs [QueueAttribute] -> Int -> QueueAttribute
forall a. HasCallStack => [a] -> Int -> a
!! Int
0)]
Int
_ -> (QueueAttribute -> Integer -> (ByteString, Maybe ByteString))
-> [QueueAttribute]
-> [Integer]
-> [(ByteString, Maybe ByteString)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\ QueueAttribute
x Integer
y -> (([ByteString] -> ByteString
B.concat [ByteString
"AttributeName.", String -> ByteString
B.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show (Integer -> String) -> Integer -> String
forall a b. (a -> b) -> a -> b
$ Integer
y]), ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
B.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ QueueAttribute -> Text
printQueueAttribute QueueAttribute
x) ) [QueueAttribute]
attrs [Integer
1 :: Integer ..]
instance SignQuery GetQueueAttributes where
type ServiceConfiguration GetQueueAttributes = SqsConfiguration
signQuery :: forall queryType.
GetQueueAttributes
-> ServiceConfiguration GetQueueAttributes queryType
-> SignatureData
-> SignedQuery
signQuery GetQueueAttributes{[QueueAttribute]
QueueName
gqaQueueName :: GetQueueAttributes -> QueueName
gqaAttributes :: GetQueueAttributes -> [QueueAttribute]
gqaQueueName :: QueueName
gqaAttributes :: [QueueAttribute]
..} = SqsQuery
-> SqsConfiguration queryType -> SignatureData -> SignedQuery
forall qt.
SqsQuery -> SqsConfiguration qt -> SignatureData -> SignedQuery
sqsSignQuery SqsQuery {
sqsQueueName :: Maybe QueueName
sqsQueueName = QueueName -> Maybe QueueName
forall a. a -> Maybe a
Just QueueName
gqaQueueName,
sqsQuery :: [(ByteString, Maybe ByteString)]
sqsQuery = [(ByteString
"Action", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"GetQueueAttributes")] [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
forall a. [a] -> [a] -> [a]
++ ([QueueAttribute] -> [(ByteString, Maybe ByteString)]
formatAttributes [QueueAttribute]
gqaAttributes)}
instance Transaction GetQueueAttributes GetQueueAttributesResponse
instance AsMemoryResponse GetQueueAttributesResponse where
type MemoryResponse GetQueueAttributesResponse = GetQueueAttributesResponse
loadToMemory :: GetQueueAttributesResponse
-> ResourceT IO (MemoryResponse GetQueueAttributesResponse)
loadToMemory = GetQueueAttributesResponse
-> ResourceT IO (MemoryResponse GetQueueAttributesResponse)
GetQueueAttributesResponse
-> ResourceT IO GetQueueAttributesResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
data SetQueueAttributes = SetQueueAttributes{
SetQueueAttributes -> QueueAttribute
sqaAttribute :: QueueAttribute,
SetQueueAttributes -> Text
sqaValue :: T.Text,
SetQueueAttributes -> QueueName
sqaQueueName :: QueueName
}deriving (Int -> SetQueueAttributes -> ShowS
[SetQueueAttributes] -> ShowS
SetQueueAttributes -> String
(Int -> SetQueueAttributes -> ShowS)
-> (SetQueueAttributes -> String)
-> ([SetQueueAttributes] -> ShowS)
-> Show SetQueueAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetQueueAttributes -> ShowS
showsPrec :: Int -> SetQueueAttributes -> ShowS
$cshow :: SetQueueAttributes -> String
show :: SetQueueAttributes -> String
$cshowList :: [SetQueueAttributes] -> ShowS
showList :: [SetQueueAttributes] -> ShowS
Show)
data SetQueueAttributesResponse = SetQueueAttributesResponse{
} deriving (Int -> SetQueueAttributesResponse -> ShowS
[SetQueueAttributesResponse] -> ShowS
SetQueueAttributesResponse -> String
(Int -> SetQueueAttributesResponse -> ShowS)
-> (SetQueueAttributesResponse -> String)
-> ([SetQueueAttributesResponse] -> ShowS)
-> Show SetQueueAttributesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetQueueAttributesResponse -> ShowS
showsPrec :: Int -> SetQueueAttributesResponse -> ShowS
$cshow :: SetQueueAttributesResponse -> String
show :: SetQueueAttributesResponse -> String
$cshowList :: [SetQueueAttributesResponse] -> ShowS
showList :: [SetQueueAttributesResponse] -> ShowS
Show)
instance ResponseConsumer r SetQueueAttributesResponse where
type ResponseMetadata SetQueueAttributesResponse = SqsMetadata
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata SetQueueAttributesResponse)
-> HTTPResponseConsumer SetQueueAttributesResponse
responseConsumer Request
_ r
_ = (Cursor -> Response SqsMetadata SetQueueAttributesResponse)
-> IORef SqsMetadata
-> HTTPResponseConsumer SetQueueAttributesResponse
forall a.
(Cursor -> Response SqsMetadata a)
-> IORef SqsMetadata -> HTTPResponseConsumer a
sqsXmlResponseConsumer Cursor -> Response SqsMetadata SetQueueAttributesResponse
forall {m :: * -> *} {p}.
Monad m =>
p -> m SetQueueAttributesResponse
parse
where
parse :: p -> m SetQueueAttributesResponse
parse p
_ = do
SetQueueAttributesResponse -> m SetQueueAttributesResponse
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return SetQueueAttributesResponse {}
instance SignQuery SetQueueAttributes where
type ServiceConfiguration SetQueueAttributes = SqsConfiguration
signQuery :: forall queryType.
SetQueueAttributes
-> ServiceConfiguration SetQueueAttributes queryType
-> SignatureData
-> SignedQuery
signQuery SetQueueAttributes {Text
QueueAttribute
QueueName
sqaAttribute :: SetQueueAttributes -> QueueAttribute
sqaValue :: SetQueueAttributes -> Text
sqaQueueName :: SetQueueAttributes -> QueueName
sqaAttribute :: QueueAttribute
sqaValue :: Text
sqaQueueName :: QueueName
..} = SqsQuery
-> SqsConfiguration queryType -> SignatureData -> SignedQuery
forall qt.
SqsQuery -> SqsConfiguration qt -> SignatureData -> SignedQuery
sqsSignQuery SqsQuery {
sqsQueueName :: Maybe QueueName
sqsQueueName = QueueName -> Maybe QueueName
forall a. a -> Maybe a
Just QueueName
sqaQueueName,
sqsQuery :: [(ByteString, Maybe ByteString)]
sqsQuery = [(ByteString
"Action", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"SetQueueAttributes"),
(ByteString
"Attribute.Name", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ QueueAttribute -> Text
printQueueAttribute QueueAttribute
sqaAttribute),
(ByteString
"Attribute.Value", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 Text
sqaValue)]}
instance Transaction SetQueueAttributes SetQueueAttributesResponse
instance AsMemoryResponse SetQueueAttributesResponse where
type MemoryResponse SetQueueAttributesResponse = SetQueueAttributesResponse
loadToMemory :: SetQueueAttributesResponse
-> ResourceT IO (MemoryResponse SetQueueAttributesResponse)
loadToMemory = SetQueueAttributesResponse
-> ResourceT IO (MemoryResponse SetQueueAttributesResponse)
SetQueueAttributesResponse
-> ResourceT IO SetQueueAttributesResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return