module Aws.SimpleDb.Commands.Select
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 Select
    = Select {
        Select -> Text
sSelectExpression :: T.Text
      , Select -> Bool
sConsistentRead :: Bool
      , Select -> Maybe Text
sNextToken :: Maybe T.Text
      }
    deriving (Int -> Select -> ShowS
[Select] -> ShowS
Select -> String
(Int -> Select -> ShowS)
-> (Select -> String) -> ([Select] -> ShowS) -> Show Select
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Select -> ShowS
showsPrec :: Int -> Select -> ShowS
$cshow :: Select -> String
show :: Select -> String
$cshowList :: [Select] -> ShowS
showList :: [Select] -> ShowS
Show)

data SelectResponse
    = SelectResponse {
        SelectResponse -> [Item [Attribute Text]]
srItems :: [Item [Attribute T.Text]]
      , SelectResponse -> Maybe Text
srNextToken :: Maybe T.Text
      }
    deriving (Int -> SelectResponse -> ShowS
[SelectResponse] -> ShowS
SelectResponse -> String
(Int -> SelectResponse -> ShowS)
-> (SelectResponse -> String)
-> ([SelectResponse] -> ShowS)
-> Show SelectResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SelectResponse -> ShowS
showsPrec :: Int -> SelectResponse -> ShowS
$cshow :: SelectResponse -> String
show :: SelectResponse -> String
$cshowList :: [SelectResponse] -> ShowS
showList :: [SelectResponse] -> ShowS
Show)

select :: T.Text -> Select
select :: Text -> Select
select Text
expr = Select { sSelectExpression :: Text
sSelectExpression = Text
expr, sConsistentRead :: Bool
sConsistentRead = Bool
False, sNextToken :: Maybe Text
sNextToken = Maybe Text
forall a. Maybe a
Nothing }

-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery Select where
    type ServiceConfiguration Select = SdbConfiguration
    signQuery :: forall queryType.
Select
-> ServiceConfiguration Select queryType
-> SignatureData
-> SignedQuery
signQuery Select{Bool
Maybe Text
Text
sSelectExpression :: Select -> Text
sConsistentRead :: Select -> Bool
sNextToken :: Select -> Maybe Text
sSelectExpression :: Text
sConsistentRead :: Bool
sNextToken :: Maybe Text
..}
        = [(ByteString, ByteString)]
-> ServiceConfiguration Select queryType
-> SignatureData
-> SignedQuery
[(ByteString, ByteString)]
-> SdbConfiguration queryType -> SignatureData -> SignedQuery
forall qt.
[(ByteString, ByteString)]
-> SdbConfiguration qt -> SignatureData -> SignedQuery
sdbSignQuery ([(ByteString, ByteString)]
 -> ServiceConfiguration Select queryType
 -> SignatureData
 -> SignedQuery)
-> ([Maybe (ByteString, ByteString)] -> [(ByteString, ByteString)])
-> [Maybe (ByteString, ByteString)]
-> ServiceConfiguration Select queryType
-> SignatureData
-> SignedQuery
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (ByteString, ByteString)]
 -> ServiceConfiguration Select queryType
 -> SignatureData
 -> SignedQuery)
-> [Maybe (ByteString, ByteString)]
-> ServiceConfiguration Select queryType
-> SignatureData
-> SignedQuery
forall a b. (a -> b) -> a -> b
$
            [ (ByteString, ByteString) -> Maybe (ByteString, ByteString)
forall a. a -> Maybe a
Just (ByteString
"Action", ByteString
"Select")
            , (ByteString, ByteString) -> Maybe (ByteString, ByteString)
forall a. a -> Maybe a
Just (ByteString
"SelectExpression", Text -> ByteString
T.encodeUtf8 Text
sSelectExpression)
            , (ByteString
"ConsistentRead", ByteString
awsTrue) (ByteString, ByteString)
-> Maybe () -> Maybe (ByteString, ByteString)
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
sConsistentRead
            , ((ByteString
"NextToken",) (ByteString -> (ByteString, ByteString))
-> (Text -> ByteString) -> Text -> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8) (Text -> (ByteString, ByteString))
-> Maybe Text -> Maybe (ByteString, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
sNextToken
            ]

instance ResponseConsumer r SelectResponse where
    type ResponseMetadata SelectResponse = SdbMetadata
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata SelectResponse)
-> HTTPResponseConsumer SelectResponse
responseConsumer Request
_ r
_ = (Cursor -> Response SdbMetadata SelectResponse)
-> IORef SdbMetadata -> HTTPResponseConsumer SelectResponse
forall a.
(Cursor -> Response SdbMetadata a)
-> IORef SdbMetadata -> HTTPResponseConsumer a
sdbResponseConsumer Cursor -> Response SdbMetadata SelectResponse
forall {m :: * -> *}. MonadThrow m => Cursor -> m SelectResponse
parse
        where parse :: Cursor -> m SelectResponse
parse Cursor
cursor = do
                () -> Text -> Cursor -> m ()
forall (m :: * -> *) a. MonadThrow m => a -> Text -> Cursor -> m a
sdbCheckResponseType () Text
"SelectResponse" Cursor
cursor
                [Item [Attribute Text]]
items <- [m (Item [Attribute Text])] -> m [Item [Attribute Text]]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([m (Item [Attribute Text])] -> m [Item [Attribute Text]])
-> [m (Item [Attribute Text])] -> m [Item [Attribute Text]]
forall a b. (a -> b) -> a -> b
$ Cursor
cursor Cursor
-> (Cursor -> [m (Item [Attribute Text])])
-> [m (Item [Attribute Text])]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Axis
Cu.laxElement Text
"Item" Axis
-> (Cursor -> m (Item [Attribute Text]))
-> Cursor
-> [m (Item [Attribute Text])]
forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| Cursor -> m (Item [Attribute Text])
forall (m :: * -> *).
MonadThrow m =>
Cursor -> m (Item [Attribute Text])
readItem
                let nextToken :: Maybe Text
nextToken = [Text] -> Maybe Text
forall a. [a] -> Maybe a
listToMaybe ([Text] -> Maybe Text) -> [Text] -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Cursor
cursor Cursor -> (Cursor -> [Text]) -> [Text]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Cursor -> [Text]
elContent Text
"NextToken"
                SelectResponse -> m SelectResponse
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (SelectResponse -> m SelectResponse)
-> SelectResponse -> m SelectResponse
forall a b. (a -> b) -> a -> b
$ [Item [Attribute Text]] -> Maybe Text -> SelectResponse
SelectResponse [Item [Attribute Text]]
items Maybe Text
nextToken

instance Transaction Select SelectResponse

instance AsMemoryResponse SelectResponse where
    type MemoryResponse SelectResponse = SelectResponse
    loadToMemory :: SelectResponse -> ResourceT IO (MemoryResponse SelectResponse)
loadToMemory = SelectResponse -> ResourceT IO (MemoryResponse SelectResponse)
SelectResponse -> ResourceT IO SelectResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return

instance ListResponse SelectResponse (Item [Attribute T.Text]) where
    listResponse :: SelectResponse -> [Item [Attribute Text]]
listResponse = SelectResponse -> [Item [Attribute Text]]
srItems

instance IteratedTransaction Select SelectResponse where
  nextIteratedRequest :: Select -> SelectResponse -> Maybe Select
nextIteratedRequest Select
req SelectResponse{srNextToken :: SelectResponse -> Maybe Text
srNextToken=Maybe Text
nt} = Select
req{sNextToken=nt} Select -> Maybe Text -> Maybe Select
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Maybe Text
nt
--  combineIteratedResponse (SelectResponse s1 _) (SelectResponse s2 nt2) = SelectResponse (s1 ++ s2) nt2