{-# 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.SDB.Select
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The @Select@ operation returns a set of attributes for @ItemNames@ that
-- match the select expression. @Select@ is similar to the standard SQL
-- SELECT statement.
--
-- The total size of the response cannot exceed 1 MB in total size. Amazon
-- SimpleDB automatically adjusts the number of items returned per page to
-- enforce this limit. For example, if the client asks to retrieve 2500
-- items, but each individual item is 10 kB in size, the system returns 100
-- items and an appropriate @NextToken@ so the client can access the next
-- page of results.
--
-- For information on how to construct select expressions, see Using Select
-- to Create Amazon SimpleDB Queries in the Developer Guide.
--
-- This operation returns paginated results.
module Amazonka.SDB.Select
  ( -- * Creating a Request
    Select (..),
    newSelect,

    -- * Request Lenses
    select_consistentRead,
    select_nextToken,
    select_selectExpression,

    -- * Destructuring the Response
    SelectResponse (..),
    newSelectResponse,

    -- * Response Lenses
    selectResponse_items,
    selectResponse_nextToken,
    selectResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSelect' smart constructor.
data Select = Select'
  { -- | Determines whether or not strong consistency should be enforced when
    -- data is read from SimpleDB. If @true@, any data previously written to
    -- SimpleDB will be returned. Otherwise, results will be consistent
    -- eventually, and the client may not see data that was written immediately
    -- before your read.
    Select -> Maybe Bool
consistentRead :: Prelude.Maybe Prelude.Bool,
    -- | A string informing Amazon SimpleDB where to start the next list of
    -- @ItemNames@.
    Select -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The expression used to query the domain.
    Select -> Text
selectExpression :: Prelude.Text
  }
  deriving (Select -> Select -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Select -> Select -> Bool
$c/= :: Select -> Select -> Bool
== :: Select -> Select -> Bool
$c== :: Select -> Select -> Bool
Prelude.Eq, ReadPrec [Select]
ReadPrec Select
Int -> ReadS Select
ReadS [Select]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Select]
$creadListPrec :: ReadPrec [Select]
readPrec :: ReadPrec Select
$creadPrec :: ReadPrec Select
readList :: ReadS [Select]
$creadList :: ReadS [Select]
readsPrec :: Int -> ReadS Select
$creadsPrec :: Int -> ReadS Select
Prelude.Read, Int -> Select -> ShowS
[Select] -> ShowS
Select -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Select] -> ShowS
$cshowList :: [Select] -> ShowS
show :: Select -> String
$cshow :: Select -> String
showsPrec :: Int -> Select -> ShowS
$cshowsPrec :: Int -> Select -> ShowS
Prelude.Show, forall x. Rep Select x -> Select
forall x. Select -> Rep Select x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Select x -> Select
$cfrom :: forall x. Select -> Rep Select x
Prelude.Generic)

-- |
-- Create a value of 'Select' 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:
--
-- 'consistentRead', 'select_consistentRead' - Determines whether or not strong consistency should be enforced when
-- data is read from SimpleDB. If @true@, any data previously written to
-- SimpleDB will be returned. Otherwise, results will be consistent
-- eventually, and the client may not see data that was written immediately
-- before your read.
--
-- 'nextToken', 'select_nextToken' - A string informing Amazon SimpleDB where to start the next list of
-- @ItemNames@.
--
-- 'selectExpression', 'select_selectExpression' - The expression used to query the domain.
newSelect ::
  -- | 'selectExpression'
  Prelude.Text ->
  Select
newSelect :: Text -> Select
newSelect Text
pSelectExpression_ =
  Select'
    { $sel:consistentRead:Select' :: Maybe Bool
consistentRead = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:Select' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:selectExpression:Select' :: Text
selectExpression = Text
pSelectExpression_
    }

-- | Determines whether or not strong consistency should be enforced when
-- data is read from SimpleDB. If @true@, any data previously written to
-- SimpleDB will be returned. Otherwise, results will be consistent
-- eventually, and the client may not see data that was written immediately
-- before your read.
select_consistentRead :: Lens.Lens' Select (Prelude.Maybe Prelude.Bool)
select_consistentRead :: Lens' Select (Maybe Bool)
select_consistentRead = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Select' {Maybe Bool
consistentRead :: Maybe Bool
$sel:consistentRead:Select' :: Select -> Maybe Bool
consistentRead} -> Maybe Bool
consistentRead) (\s :: Select
s@Select' {} Maybe Bool
a -> Select
s {$sel:consistentRead:Select' :: Maybe Bool
consistentRead = Maybe Bool
a} :: Select)

-- | A string informing Amazon SimpleDB where to start the next list of
-- @ItemNames@.
select_nextToken :: Lens.Lens' Select (Prelude.Maybe Prelude.Text)
select_nextToken :: Lens' Select (Maybe Text)
select_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Select' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:Select' :: Select -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: Select
s@Select' {} Maybe Text
a -> Select
s {$sel:nextToken:Select' :: Maybe Text
nextToken = Maybe Text
a} :: Select)

-- | The expression used to query the domain.
select_selectExpression :: Lens.Lens' Select Prelude.Text
select_selectExpression :: Lens' Select Text
select_selectExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Select' {Text
selectExpression :: Text
$sel:selectExpression:Select' :: Select -> Text
selectExpression} -> Text
selectExpression) (\s :: Select
s@Select' {} Text
a -> Select
s {$sel:selectExpression:Select' :: Text
selectExpression = Text
a} :: Select)

instance Core.AWSPager Select where
  page :: Select -> AWSResponse Select -> Maybe Select
page Select
rq AWSResponse Select
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse Select
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SelectResponse (Maybe Text)
selectResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse Select
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SelectResponse (Maybe [Item])
selectResponse_items
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ Select
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' Select (Maybe Text)
select_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse Select
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SelectResponse (Maybe Text)
selectResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest Select where
  type AWSResponse Select = SelectResponse
  request :: (Service -> Service) -> Select -> Request Select
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy Select
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse Select)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"SelectResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Item] -> Maybe Text -> Int -> SelectResponse
SelectResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"Item") [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextToken")
            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 Select where
  hashWithSalt :: Int -> Select -> Int
hashWithSalt Int
_salt Select' {Maybe Bool
Maybe Text
Text
selectExpression :: Text
nextToken :: Maybe Text
consistentRead :: Maybe Bool
$sel:selectExpression:Select' :: Select -> Text
$sel:nextToken:Select' :: Select -> Maybe Text
$sel:consistentRead:Select' :: Select -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
consistentRead
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
selectExpression

instance Prelude.NFData Select where
  rnf :: Select -> ()
rnf Select' {Maybe Bool
Maybe Text
Text
selectExpression :: Text
nextToken :: Maybe Text
consistentRead :: Maybe Bool
$sel:selectExpression:Select' :: Select -> Text
$sel:nextToken:Select' :: Select -> Maybe Text
$sel:consistentRead:Select' :: Select -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
consistentRead
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
selectExpression

instance Data.ToHeaders Select where
  toHeaders :: Select -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery Select where
  toQuery :: Select -> QueryString
toQuery Select' {Maybe Bool
Maybe Text
Text
selectExpression :: Text
nextToken :: Maybe Text
consistentRead :: Maybe Bool
$sel:selectExpression:Select' :: Select -> Text
$sel:nextToken:Select' :: Select -> Maybe Text
$sel:consistentRead:Select' :: Select -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"Select" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2009-04-15" :: Prelude.ByteString),
        ByteString
"ConsistentRead" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
consistentRead,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"SelectExpression" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
selectExpression
      ]

-- | /See:/ 'newSelectResponse' smart constructor.
data SelectResponse = SelectResponse'
  { -- | A list of items that match the select expression.
    SelectResponse -> Maybe [Item]
items :: Prelude.Maybe [Item],
    -- | An opaque token indicating that more items than @MaxNumberOfItems@ were
    -- matched, the response size exceeded 1 megabyte, or the execution time
    -- exceeded 5 seconds.
    SelectResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    SelectResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SelectResponse -> SelectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectResponse -> SelectResponse -> Bool
$c/= :: SelectResponse -> SelectResponse -> Bool
== :: SelectResponse -> SelectResponse -> Bool
$c== :: SelectResponse -> SelectResponse -> Bool
Prelude.Eq, ReadPrec [SelectResponse]
ReadPrec SelectResponse
Int -> ReadS SelectResponse
ReadS [SelectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SelectResponse]
$creadListPrec :: ReadPrec [SelectResponse]
readPrec :: ReadPrec SelectResponse
$creadPrec :: ReadPrec SelectResponse
readList :: ReadS [SelectResponse]
$creadList :: ReadS [SelectResponse]
readsPrec :: Int -> ReadS SelectResponse
$creadsPrec :: Int -> ReadS SelectResponse
Prelude.Read, Int -> SelectResponse -> ShowS
[SelectResponse] -> ShowS
SelectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectResponse] -> ShowS
$cshowList :: [SelectResponse] -> ShowS
show :: SelectResponse -> String
$cshow :: SelectResponse -> String
showsPrec :: Int -> SelectResponse -> ShowS
$cshowsPrec :: Int -> SelectResponse -> ShowS
Prelude.Show, forall x. Rep SelectResponse x -> SelectResponse
forall x. SelectResponse -> Rep SelectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectResponse x -> SelectResponse
$cfrom :: forall x. SelectResponse -> Rep SelectResponse x
Prelude.Generic)

-- |
-- Create a value of 'SelectResponse' 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:
--
-- 'items', 'selectResponse_items' - A list of items that match the select expression.
--
-- 'nextToken', 'selectResponse_nextToken' - An opaque token indicating that more items than @MaxNumberOfItems@ were
-- matched, the response size exceeded 1 megabyte, or the execution time
-- exceeded 5 seconds.
--
-- 'httpStatus', 'selectResponse_httpStatus' - The response's http status code.
newSelectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SelectResponse
newSelectResponse :: Int -> SelectResponse
newSelectResponse Int
pHttpStatus_ =
  SelectResponse'
    { $sel:items:SelectResponse' :: Maybe [Item]
items = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SelectResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SelectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of items that match the select expression.
selectResponse_items :: Lens.Lens' SelectResponse (Prelude.Maybe [Item])
selectResponse_items :: Lens' SelectResponse (Maybe [Item])
selectResponse_items = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SelectResponse' {Maybe [Item]
items :: Maybe [Item]
$sel:items:SelectResponse' :: SelectResponse -> Maybe [Item]
items} -> Maybe [Item]
items) (\s :: SelectResponse
s@SelectResponse' {} Maybe [Item]
a -> SelectResponse
s {$sel:items:SelectResponse' :: Maybe [Item]
items = Maybe [Item]
a} :: SelectResponse) 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

-- | An opaque token indicating that more items than @MaxNumberOfItems@ were
-- matched, the response size exceeded 1 megabyte, or the execution time
-- exceeded 5 seconds.
selectResponse_nextToken :: Lens.Lens' SelectResponse (Prelude.Maybe Prelude.Text)
selectResponse_nextToken :: Lens' SelectResponse (Maybe Text)
selectResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SelectResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SelectResponse' :: SelectResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SelectResponse
s@SelectResponse' {} Maybe Text
a -> SelectResponse
s {$sel:nextToken:SelectResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SelectResponse)

-- | The response's http status code.
selectResponse_httpStatus :: Lens.Lens' SelectResponse Prelude.Int
selectResponse_httpStatus :: Lens' SelectResponse Int
selectResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SelectResponse' {Int
httpStatus :: Int
$sel:httpStatus:SelectResponse' :: SelectResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SelectResponse
s@SelectResponse' {} Int
a -> SelectResponse
s {$sel:httpStatus:SelectResponse' :: Int
httpStatus = Int
a} :: SelectResponse)

instance Prelude.NFData SelectResponse where
  rnf :: SelectResponse -> ()
rnf SelectResponse' {Int
Maybe [Item]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
items :: Maybe [Item]
$sel:httpStatus:SelectResponse' :: SelectResponse -> Int
$sel:nextToken:SelectResponse' :: SelectResponse -> Maybe Text
$sel:items:SelectResponse' :: SelectResponse -> Maybe [Item]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Item]
items
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus