{-# 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.GetAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns all of the attributes associated with the specified item.
-- Optionally, the attributes returned can be limited to one or more
-- attributes by specifying an attribute name parameter.
--
-- If the item does not exist on the replica that was accessed for this
-- operation, an empty set is returned. The system does not return an error
-- as it cannot guarantee the item does not exist on other replicas.
module Amazonka.SDB.GetAttributes
  ( -- * Creating a Request
    GetAttributes (..),
    newGetAttributes,

    -- * Request Lenses
    getAttributes_attributeNames,
    getAttributes_consistentRead,
    getAttributes_domainName,
    getAttributes_itemName,

    -- * Destructuring the Response
    GetAttributesResponse (..),
    newGetAttributesResponse,

    -- * Response Lenses
    getAttributesResponse_attributes,
    getAttributesResponse_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:/ 'newGetAttributes' smart constructor.
data GetAttributes = GetAttributes'
  { -- | The names of the attributes.
    GetAttributes -> Maybe [Text]
attributeNames :: Prelude.Maybe [Prelude.Text],
    -- | 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.
    GetAttributes -> Maybe Bool
consistentRead :: Prelude.Maybe Prelude.Bool,
    -- | The name of the domain in which to perform the operation.
    GetAttributes -> Text
domainName :: Prelude.Text,
    -- | The name of the item.
    GetAttributes -> Text
itemName :: Prelude.Text
  }
  deriving (GetAttributes -> GetAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAttributes -> GetAttributes -> Bool
$c/= :: GetAttributes -> GetAttributes -> Bool
== :: GetAttributes -> GetAttributes -> Bool
$c== :: GetAttributes -> GetAttributes -> Bool
Prelude.Eq, ReadPrec [GetAttributes]
ReadPrec GetAttributes
Int -> ReadS GetAttributes
ReadS [GetAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAttributes]
$creadListPrec :: ReadPrec [GetAttributes]
readPrec :: ReadPrec GetAttributes
$creadPrec :: ReadPrec GetAttributes
readList :: ReadS [GetAttributes]
$creadList :: ReadS [GetAttributes]
readsPrec :: Int -> ReadS GetAttributes
$creadsPrec :: Int -> ReadS GetAttributes
Prelude.Read, 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
Prelude.Show, forall x. Rep GetAttributes x -> GetAttributes
forall x. GetAttributes -> Rep GetAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAttributes x -> GetAttributes
$cfrom :: forall x. GetAttributes -> Rep GetAttributes x
Prelude.Generic)

-- |
-- Create a value of 'GetAttributes' 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:
--
-- 'attributeNames', 'getAttributes_attributeNames' - The names of the attributes.
--
-- 'consistentRead', 'getAttributes_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.
--
-- 'domainName', 'getAttributes_domainName' - The name of the domain in which to perform the operation.
--
-- 'itemName', 'getAttributes_itemName' - The name of the item.
newGetAttributes ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'itemName'
  Prelude.Text ->
  GetAttributes
newGetAttributes :: Text -> Text -> GetAttributes
newGetAttributes Text
pDomainName_ Text
pItemName_ =
  GetAttributes'
    { $sel:attributeNames:GetAttributes' :: Maybe [Text]
attributeNames = forall a. Maybe a
Prelude.Nothing,
      $sel:consistentRead:GetAttributes' :: Maybe Bool
consistentRead = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:GetAttributes' :: Text
domainName = Text
pDomainName_,
      $sel:itemName:GetAttributes' :: Text
itemName = Text
pItemName_
    }

-- | The names of the attributes.
getAttributes_attributeNames :: Lens.Lens' GetAttributes (Prelude.Maybe [Prelude.Text])
getAttributes_attributeNames :: Lens' GetAttributes (Maybe [Text])
getAttributes_attributeNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAttributes' {Maybe [Text]
attributeNames :: Maybe [Text]
$sel:attributeNames:GetAttributes' :: GetAttributes -> Maybe [Text]
attributeNames} -> Maybe [Text]
attributeNames) (\s :: GetAttributes
s@GetAttributes' {} Maybe [Text]
a -> GetAttributes
s {$sel:attributeNames:GetAttributes' :: Maybe [Text]
attributeNames = Maybe [Text]
a} :: GetAttributes) 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

-- | 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.
getAttributes_consistentRead :: Lens.Lens' GetAttributes (Prelude.Maybe Prelude.Bool)
getAttributes_consistentRead :: Lens' GetAttributes (Maybe Bool)
getAttributes_consistentRead = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAttributes' {Maybe Bool
consistentRead :: Maybe Bool
$sel:consistentRead:GetAttributes' :: GetAttributes -> Maybe Bool
consistentRead} -> Maybe Bool
consistentRead) (\s :: GetAttributes
s@GetAttributes' {} Maybe Bool
a -> GetAttributes
s {$sel:consistentRead:GetAttributes' :: Maybe Bool
consistentRead = Maybe Bool
a} :: GetAttributes)

-- | The name of the domain in which to perform the operation.
getAttributes_domainName :: Lens.Lens' GetAttributes Prelude.Text
getAttributes_domainName :: Lens' GetAttributes Text
getAttributes_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAttributes' {Text
domainName :: Text
$sel:domainName:GetAttributes' :: GetAttributes -> Text
domainName} -> Text
domainName) (\s :: GetAttributes
s@GetAttributes' {} Text
a -> GetAttributes
s {$sel:domainName:GetAttributes' :: Text
domainName = Text
a} :: GetAttributes)

-- | The name of the item.
getAttributes_itemName :: Lens.Lens' GetAttributes Prelude.Text
getAttributes_itemName :: Lens' GetAttributes Text
getAttributes_itemName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAttributes' {Text
itemName :: Text
$sel:itemName:GetAttributes' :: GetAttributes -> Text
itemName} -> Text
itemName) (\s :: GetAttributes
s@GetAttributes' {} Text
a -> GetAttributes
s {$sel:itemName:GetAttributes' :: Text
itemName = Text
a} :: GetAttributes)

instance Core.AWSRequest GetAttributes where
  type
    AWSResponse GetAttributes =
      GetAttributesResponse
  request :: (Service -> Service) -> GetAttributes -> Request GetAttributes
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 GetAttributes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetAttributes)))
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
"GetAttributesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Attribute] -> Int -> GetAttributesResponse
GetAttributesResponse'
            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
"Attribute") [Node]
x)
            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 GetAttributes where
  hashWithSalt :: Int -> GetAttributes -> Int
hashWithSalt Int
_salt GetAttributes' {Maybe Bool
Maybe [Text]
Text
itemName :: Text
domainName :: Text
consistentRead :: Maybe Bool
attributeNames :: Maybe [Text]
$sel:itemName:GetAttributes' :: GetAttributes -> Text
$sel:domainName:GetAttributes' :: GetAttributes -> Text
$sel:consistentRead:GetAttributes' :: GetAttributes -> Maybe Bool
$sel:attributeNames:GetAttributes' :: GetAttributes -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
attributeNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
consistentRead
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
itemName

instance Prelude.NFData GetAttributes where
  rnf :: GetAttributes -> ()
rnf GetAttributes' {Maybe Bool
Maybe [Text]
Text
itemName :: Text
domainName :: Text
consistentRead :: Maybe Bool
attributeNames :: Maybe [Text]
$sel:itemName:GetAttributes' :: GetAttributes -> Text
$sel:domainName:GetAttributes' :: GetAttributes -> Text
$sel:consistentRead:GetAttributes' :: GetAttributes -> Maybe Bool
$sel:attributeNames:GetAttributes' :: GetAttributes -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
attributeNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
itemName

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

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

instance Data.ToQuery GetAttributes where
  toQuery :: GetAttributes -> QueryString
toQuery GetAttributes' {Maybe Bool
Maybe [Text]
Text
itemName :: Text
domainName :: Text
consistentRead :: Maybe Bool
attributeNames :: Maybe [Text]
$sel:itemName:GetAttributes' :: GetAttributes -> Text
$sel:domainName:GetAttributes' :: GetAttributes -> Text
$sel:consistentRead:GetAttributes' :: GetAttributes -> Maybe Bool
$sel:attributeNames:GetAttributes' :: GetAttributes -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetAttributes" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2009-04-15" :: Prelude.ByteString),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AttributeName"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
attributeNames
          ),
        ByteString
"ConsistentRead" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
consistentRead,
        ByteString
"DomainName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domainName,
        ByteString
"ItemName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
itemName
      ]

-- | /See:/ 'newGetAttributesResponse' smart constructor.
data GetAttributesResponse = GetAttributesResponse'
  { -- | The list of attributes returned by the operation.
    GetAttributesResponse -> Maybe [Attribute]
attributes :: Prelude.Maybe [Attribute],
    -- | The response's http status code.
    GetAttributesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAttributesResponse -> GetAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAttributesResponse -> GetAttributesResponse -> Bool
$c/= :: GetAttributesResponse -> GetAttributesResponse -> Bool
== :: GetAttributesResponse -> GetAttributesResponse -> Bool
$c== :: GetAttributesResponse -> GetAttributesResponse -> Bool
Prelude.Eq, ReadPrec [GetAttributesResponse]
ReadPrec GetAttributesResponse
Int -> ReadS GetAttributesResponse
ReadS [GetAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAttributesResponse]
$creadListPrec :: ReadPrec [GetAttributesResponse]
readPrec :: ReadPrec GetAttributesResponse
$creadPrec :: ReadPrec GetAttributesResponse
readList :: ReadS [GetAttributesResponse]
$creadList :: ReadS [GetAttributesResponse]
readsPrec :: Int -> ReadS GetAttributesResponse
$creadsPrec :: Int -> ReadS GetAttributesResponse
Prelude.Read, 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
Prelude.Show, forall x. Rep GetAttributesResponse x -> GetAttributesResponse
forall x. GetAttributesResponse -> Rep GetAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAttributesResponse x -> GetAttributesResponse
$cfrom :: forall x. GetAttributesResponse -> Rep GetAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAttributesResponse' 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:
--
-- 'attributes', 'getAttributesResponse_attributes' - The list of attributes returned by the operation.
--
-- 'httpStatus', 'getAttributesResponse_httpStatus' - The response's http status code.
newGetAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAttributesResponse
newGetAttributesResponse :: Int -> GetAttributesResponse
newGetAttributesResponse Int
pHttpStatus_ =
  GetAttributesResponse'
    { $sel:attributes:GetAttributesResponse' :: Maybe [Attribute]
attributes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of attributes returned by the operation.
getAttributesResponse_attributes :: Lens.Lens' GetAttributesResponse (Prelude.Maybe [Attribute])
getAttributesResponse_attributes :: Lens' GetAttributesResponse (Maybe [Attribute])
getAttributesResponse_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAttributesResponse' {Maybe [Attribute]
attributes :: Maybe [Attribute]
$sel:attributes:GetAttributesResponse' :: GetAttributesResponse -> Maybe [Attribute]
attributes} -> Maybe [Attribute]
attributes) (\s :: GetAttributesResponse
s@GetAttributesResponse' {} Maybe [Attribute]
a -> GetAttributesResponse
s {$sel:attributes:GetAttributesResponse' :: Maybe [Attribute]
attributes = Maybe [Attribute]
a} :: GetAttributesResponse) 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

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

instance Prelude.NFData GetAttributesResponse where
  rnf :: GetAttributesResponse -> ()
rnf GetAttributesResponse' {Int
Maybe [Attribute]
httpStatus :: Int
attributes :: Maybe [Attribute]
$sel:httpStatus:GetAttributesResponse' :: GetAttributesResponse -> Int
$sel:attributes:GetAttributesResponse' :: GetAttributesResponse -> Maybe [Attribute]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Attribute]
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus