{-# 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.CloudDirectory.UpdateObjectAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a given object\'s attributes.
module Amazonka.CloudDirectory.UpdateObjectAttributes
  ( -- * Creating a Request
    UpdateObjectAttributes (..),
    newUpdateObjectAttributes,

    -- * Request Lenses
    updateObjectAttributes_directoryArn,
    updateObjectAttributes_objectReference,
    updateObjectAttributes_attributeUpdates,

    -- * Destructuring the Response
    UpdateObjectAttributesResponse (..),
    newUpdateObjectAttributesResponse,

    -- * Response Lenses
    updateObjectAttributesResponse_objectIdentifier,
    updateObjectAttributesResponse_httpStatus,
  )
where

import Amazonka.CloudDirectory.Types
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

-- | /See:/ 'newUpdateObjectAttributes' smart constructor.
data UpdateObjectAttributes = UpdateObjectAttributes'
  { -- | The Amazon Resource Name (ARN) that is associated with the Directory
    -- where the object resides. For more information, see arns.
    UpdateObjectAttributes -> Text
directoryArn :: Prelude.Text,
    -- | The reference that identifies the object.
    UpdateObjectAttributes -> ObjectReference
objectReference :: ObjectReference,
    -- | The attributes update structure.
    UpdateObjectAttributes -> [ObjectAttributeUpdate]
attributeUpdates :: [ObjectAttributeUpdate]
  }
  deriving (UpdateObjectAttributes -> UpdateObjectAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateObjectAttributes -> UpdateObjectAttributes -> Bool
$c/= :: UpdateObjectAttributes -> UpdateObjectAttributes -> Bool
== :: UpdateObjectAttributes -> UpdateObjectAttributes -> Bool
$c== :: UpdateObjectAttributes -> UpdateObjectAttributes -> Bool
Prelude.Eq, ReadPrec [UpdateObjectAttributes]
ReadPrec UpdateObjectAttributes
Int -> ReadS UpdateObjectAttributes
ReadS [UpdateObjectAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateObjectAttributes]
$creadListPrec :: ReadPrec [UpdateObjectAttributes]
readPrec :: ReadPrec UpdateObjectAttributes
$creadPrec :: ReadPrec UpdateObjectAttributes
readList :: ReadS [UpdateObjectAttributes]
$creadList :: ReadS [UpdateObjectAttributes]
readsPrec :: Int -> ReadS UpdateObjectAttributes
$creadsPrec :: Int -> ReadS UpdateObjectAttributes
Prelude.Read, Int -> UpdateObjectAttributes -> ShowS
[UpdateObjectAttributes] -> ShowS
UpdateObjectAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateObjectAttributes] -> ShowS
$cshowList :: [UpdateObjectAttributes] -> ShowS
show :: UpdateObjectAttributes -> String
$cshow :: UpdateObjectAttributes -> String
showsPrec :: Int -> UpdateObjectAttributes -> ShowS
$cshowsPrec :: Int -> UpdateObjectAttributes -> ShowS
Prelude.Show, forall x. Rep UpdateObjectAttributes x -> UpdateObjectAttributes
forall x. UpdateObjectAttributes -> Rep UpdateObjectAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateObjectAttributes x -> UpdateObjectAttributes
$cfrom :: forall x. UpdateObjectAttributes -> Rep UpdateObjectAttributes x
Prelude.Generic)

-- |
-- Create a value of 'UpdateObjectAttributes' 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:
--
-- 'directoryArn', 'updateObjectAttributes_directoryArn' - The Amazon Resource Name (ARN) that is associated with the Directory
-- where the object resides. For more information, see arns.
--
-- 'objectReference', 'updateObjectAttributes_objectReference' - The reference that identifies the object.
--
-- 'attributeUpdates', 'updateObjectAttributes_attributeUpdates' - The attributes update structure.
newUpdateObjectAttributes ::
  -- | 'directoryArn'
  Prelude.Text ->
  -- | 'objectReference'
  ObjectReference ->
  UpdateObjectAttributes
newUpdateObjectAttributes :: Text -> ObjectReference -> UpdateObjectAttributes
newUpdateObjectAttributes
  Text
pDirectoryArn_
  ObjectReference
pObjectReference_ =
    UpdateObjectAttributes'
      { $sel:directoryArn:UpdateObjectAttributes' :: Text
directoryArn =
          Text
pDirectoryArn_,
        $sel:objectReference:UpdateObjectAttributes' :: ObjectReference
objectReference = ObjectReference
pObjectReference_,
        $sel:attributeUpdates:UpdateObjectAttributes' :: [ObjectAttributeUpdate]
attributeUpdates = forall a. Monoid a => a
Prelude.mempty
      }

-- | The Amazon Resource Name (ARN) that is associated with the Directory
-- where the object resides. For more information, see arns.
updateObjectAttributes_directoryArn :: Lens.Lens' UpdateObjectAttributes Prelude.Text
updateObjectAttributes_directoryArn :: Lens' UpdateObjectAttributes Text
updateObjectAttributes_directoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateObjectAttributes' {Text
directoryArn :: Text
$sel:directoryArn:UpdateObjectAttributes' :: UpdateObjectAttributes -> Text
directoryArn} -> Text
directoryArn) (\s :: UpdateObjectAttributes
s@UpdateObjectAttributes' {} Text
a -> UpdateObjectAttributes
s {$sel:directoryArn:UpdateObjectAttributes' :: Text
directoryArn = Text
a} :: UpdateObjectAttributes)

-- | The reference that identifies the object.
updateObjectAttributes_objectReference :: Lens.Lens' UpdateObjectAttributes ObjectReference
updateObjectAttributes_objectReference :: Lens' UpdateObjectAttributes ObjectReference
updateObjectAttributes_objectReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateObjectAttributes' {ObjectReference
objectReference :: ObjectReference
$sel:objectReference:UpdateObjectAttributes' :: UpdateObjectAttributes -> ObjectReference
objectReference} -> ObjectReference
objectReference) (\s :: UpdateObjectAttributes
s@UpdateObjectAttributes' {} ObjectReference
a -> UpdateObjectAttributes
s {$sel:objectReference:UpdateObjectAttributes' :: ObjectReference
objectReference = ObjectReference
a} :: UpdateObjectAttributes)

-- | The attributes update structure.
updateObjectAttributes_attributeUpdates :: Lens.Lens' UpdateObjectAttributes [ObjectAttributeUpdate]
updateObjectAttributes_attributeUpdates :: Lens' UpdateObjectAttributes [ObjectAttributeUpdate]
updateObjectAttributes_attributeUpdates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateObjectAttributes' {[ObjectAttributeUpdate]
attributeUpdates :: [ObjectAttributeUpdate]
$sel:attributeUpdates:UpdateObjectAttributes' :: UpdateObjectAttributes -> [ObjectAttributeUpdate]
attributeUpdates} -> [ObjectAttributeUpdate]
attributeUpdates) (\s :: UpdateObjectAttributes
s@UpdateObjectAttributes' {} [ObjectAttributeUpdate]
a -> UpdateObjectAttributes
s {$sel:attributeUpdates:UpdateObjectAttributes' :: [ObjectAttributeUpdate]
attributeUpdates = [ObjectAttributeUpdate]
a} :: UpdateObjectAttributes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest UpdateObjectAttributes where
  type
    AWSResponse UpdateObjectAttributes =
      UpdateObjectAttributesResponse
  request :: (Service -> Service)
-> UpdateObjectAttributes -> Request UpdateObjectAttributes
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateObjectAttributes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateObjectAttributes)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> UpdateObjectAttributesResponse
UpdateObjectAttributesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ObjectIdentifier")
            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 UpdateObjectAttributes where
  hashWithSalt :: Int -> UpdateObjectAttributes -> Int
hashWithSalt Int
_salt UpdateObjectAttributes' {[ObjectAttributeUpdate]
Text
ObjectReference
attributeUpdates :: [ObjectAttributeUpdate]
objectReference :: ObjectReference
directoryArn :: Text
$sel:attributeUpdates:UpdateObjectAttributes' :: UpdateObjectAttributes -> [ObjectAttributeUpdate]
$sel:objectReference:UpdateObjectAttributes' :: UpdateObjectAttributes -> ObjectReference
$sel:directoryArn:UpdateObjectAttributes' :: UpdateObjectAttributes -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectReference
objectReference
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [ObjectAttributeUpdate]
attributeUpdates

instance Prelude.NFData UpdateObjectAttributes where
  rnf :: UpdateObjectAttributes -> ()
rnf UpdateObjectAttributes' {[ObjectAttributeUpdate]
Text
ObjectReference
attributeUpdates :: [ObjectAttributeUpdate]
objectReference :: ObjectReference
directoryArn :: Text
$sel:attributeUpdates:UpdateObjectAttributes' :: UpdateObjectAttributes -> [ObjectAttributeUpdate]
$sel:objectReference:UpdateObjectAttributes' :: UpdateObjectAttributes -> ObjectReference
$sel:directoryArn:UpdateObjectAttributes' :: UpdateObjectAttributes -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
directoryArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectReference
objectReference
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ObjectAttributeUpdate]
attributeUpdates

instance Data.ToHeaders UpdateObjectAttributes where
  toHeaders :: UpdateObjectAttributes -> ResponseHeaders
toHeaders UpdateObjectAttributes' {[ObjectAttributeUpdate]
Text
ObjectReference
attributeUpdates :: [ObjectAttributeUpdate]
objectReference :: ObjectReference
directoryArn :: Text
$sel:attributeUpdates:UpdateObjectAttributes' :: UpdateObjectAttributes -> [ObjectAttributeUpdate]
$sel:objectReference:UpdateObjectAttributes' :: UpdateObjectAttributes -> ObjectReference
$sel:directoryArn:UpdateObjectAttributes' :: UpdateObjectAttributes -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amz-data-partition" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
directoryArn]

instance Data.ToJSON UpdateObjectAttributes where
  toJSON :: UpdateObjectAttributes -> Value
toJSON UpdateObjectAttributes' {[ObjectAttributeUpdate]
Text
ObjectReference
attributeUpdates :: [ObjectAttributeUpdate]
objectReference :: ObjectReference
directoryArn :: Text
$sel:attributeUpdates:UpdateObjectAttributes' :: UpdateObjectAttributes -> [ObjectAttributeUpdate]
$sel:objectReference:UpdateObjectAttributes' :: UpdateObjectAttributes -> ObjectReference
$sel:directoryArn:UpdateObjectAttributes' :: UpdateObjectAttributes -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ObjectReference" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ObjectReference
objectReference),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AttributeUpdates" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [ObjectAttributeUpdate]
attributeUpdates)
          ]
      )

instance Data.ToPath UpdateObjectAttributes where
  toPath :: UpdateObjectAttributes -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/object/update"

instance Data.ToQuery UpdateObjectAttributes where
  toQuery :: UpdateObjectAttributes -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateObjectAttributesResponse' smart constructor.
data UpdateObjectAttributesResponse = UpdateObjectAttributesResponse'
  { -- | The @ObjectIdentifier@ of the updated object.
    UpdateObjectAttributesResponse -> Maybe Text
objectIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateObjectAttributesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateObjectAttributesResponse
-> UpdateObjectAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateObjectAttributesResponse
-> UpdateObjectAttributesResponse -> Bool
$c/= :: UpdateObjectAttributesResponse
-> UpdateObjectAttributesResponse -> Bool
== :: UpdateObjectAttributesResponse
-> UpdateObjectAttributesResponse -> Bool
$c== :: UpdateObjectAttributesResponse
-> UpdateObjectAttributesResponse -> Bool
Prelude.Eq, ReadPrec [UpdateObjectAttributesResponse]
ReadPrec UpdateObjectAttributesResponse
Int -> ReadS UpdateObjectAttributesResponse
ReadS [UpdateObjectAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateObjectAttributesResponse]
$creadListPrec :: ReadPrec [UpdateObjectAttributesResponse]
readPrec :: ReadPrec UpdateObjectAttributesResponse
$creadPrec :: ReadPrec UpdateObjectAttributesResponse
readList :: ReadS [UpdateObjectAttributesResponse]
$creadList :: ReadS [UpdateObjectAttributesResponse]
readsPrec :: Int -> ReadS UpdateObjectAttributesResponse
$creadsPrec :: Int -> ReadS UpdateObjectAttributesResponse
Prelude.Read, Int -> UpdateObjectAttributesResponse -> ShowS
[UpdateObjectAttributesResponse] -> ShowS
UpdateObjectAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateObjectAttributesResponse] -> ShowS
$cshowList :: [UpdateObjectAttributesResponse] -> ShowS
show :: UpdateObjectAttributesResponse -> String
$cshow :: UpdateObjectAttributesResponse -> String
showsPrec :: Int -> UpdateObjectAttributesResponse -> ShowS
$cshowsPrec :: Int -> UpdateObjectAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateObjectAttributesResponse x
-> UpdateObjectAttributesResponse
forall x.
UpdateObjectAttributesResponse
-> Rep UpdateObjectAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateObjectAttributesResponse x
-> UpdateObjectAttributesResponse
$cfrom :: forall x.
UpdateObjectAttributesResponse
-> Rep UpdateObjectAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateObjectAttributesResponse' 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:
--
-- 'objectIdentifier', 'updateObjectAttributesResponse_objectIdentifier' - The @ObjectIdentifier@ of the updated object.
--
-- 'httpStatus', 'updateObjectAttributesResponse_httpStatus' - The response's http status code.
newUpdateObjectAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateObjectAttributesResponse
newUpdateObjectAttributesResponse :: Int -> UpdateObjectAttributesResponse
newUpdateObjectAttributesResponse Int
pHttpStatus_ =
  UpdateObjectAttributesResponse'
    { $sel:objectIdentifier:UpdateObjectAttributesResponse' :: Maybe Text
objectIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateObjectAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @ObjectIdentifier@ of the updated object.
updateObjectAttributesResponse_objectIdentifier :: Lens.Lens' UpdateObjectAttributesResponse (Prelude.Maybe Prelude.Text)
updateObjectAttributesResponse_objectIdentifier :: Lens' UpdateObjectAttributesResponse (Maybe Text)
updateObjectAttributesResponse_objectIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateObjectAttributesResponse' {Maybe Text
objectIdentifier :: Maybe Text
$sel:objectIdentifier:UpdateObjectAttributesResponse' :: UpdateObjectAttributesResponse -> Maybe Text
objectIdentifier} -> Maybe Text
objectIdentifier) (\s :: UpdateObjectAttributesResponse
s@UpdateObjectAttributesResponse' {} Maybe Text
a -> UpdateObjectAttributesResponse
s {$sel:objectIdentifier:UpdateObjectAttributesResponse' :: Maybe Text
objectIdentifier = Maybe Text
a} :: UpdateObjectAttributesResponse)

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

instance
  Prelude.NFData
    UpdateObjectAttributesResponse
  where
  rnf :: UpdateObjectAttributesResponse -> ()
rnf UpdateObjectAttributesResponse' {Int
Maybe Text
httpStatus :: Int
objectIdentifier :: Maybe Text
$sel:httpStatus:UpdateObjectAttributesResponse' :: UpdateObjectAttributesResponse -> Int
$sel:objectIdentifier:UpdateObjectAttributesResponse' :: UpdateObjectAttributesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
objectIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus