{-# 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.IdentityStore.UpdateUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- For the specified user in the specified identity store, updates the user
-- metadata and attributes.
module Amazonka.IdentityStore.UpdateUser
  ( -- * Creating a Request
    UpdateUser (..),
    newUpdateUser,

    -- * Request Lenses
    updateUser_identityStoreId,
    updateUser_userId,
    updateUser_operations,

    -- * Destructuring the Response
    UpdateUserResponse (..),
    newUpdateUserResponse,

    -- * Response Lenses
    updateUserResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateUser' smart constructor.
data UpdateUser = UpdateUser'
  { -- | The globally unique identifier for the identity store.
    UpdateUser -> Text
identityStoreId :: Prelude.Text,
    -- | The identifier for a user in the identity store.
    UpdateUser -> Text
userId :: Prelude.Text,
    -- | A list of @AttributeOperation@ objects to apply to the requested user.
    -- These operations might add, replace, or remove an attribute.
    UpdateUser -> NonEmpty AttributeOperation
operations :: Prelude.NonEmpty AttributeOperation
  }
  deriving (UpdateUser -> UpdateUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUser -> UpdateUser -> Bool
$c/= :: UpdateUser -> UpdateUser -> Bool
== :: UpdateUser -> UpdateUser -> Bool
$c== :: UpdateUser -> UpdateUser -> Bool
Prelude.Eq, ReadPrec [UpdateUser]
ReadPrec UpdateUser
Int -> ReadS UpdateUser
ReadS [UpdateUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUser]
$creadListPrec :: ReadPrec [UpdateUser]
readPrec :: ReadPrec UpdateUser
$creadPrec :: ReadPrec UpdateUser
readList :: ReadS [UpdateUser]
$creadList :: ReadS [UpdateUser]
readsPrec :: Int -> ReadS UpdateUser
$creadsPrec :: Int -> ReadS UpdateUser
Prelude.Read, Int -> UpdateUser -> ShowS
[UpdateUser] -> ShowS
UpdateUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUser] -> ShowS
$cshowList :: [UpdateUser] -> ShowS
show :: UpdateUser -> String
$cshow :: UpdateUser -> String
showsPrec :: Int -> UpdateUser -> ShowS
$cshowsPrec :: Int -> UpdateUser -> ShowS
Prelude.Show, forall x. Rep UpdateUser x -> UpdateUser
forall x. UpdateUser -> Rep UpdateUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUser x -> UpdateUser
$cfrom :: forall x. UpdateUser -> Rep UpdateUser x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUser' 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:
--
-- 'identityStoreId', 'updateUser_identityStoreId' - The globally unique identifier for the identity store.
--
-- 'userId', 'updateUser_userId' - The identifier for a user in the identity store.
--
-- 'operations', 'updateUser_operations' - A list of @AttributeOperation@ objects to apply to the requested user.
-- These operations might add, replace, or remove an attribute.
newUpdateUser ::
  -- | 'identityStoreId'
  Prelude.Text ->
  -- | 'userId'
  Prelude.Text ->
  -- | 'operations'
  Prelude.NonEmpty AttributeOperation ->
  UpdateUser
newUpdateUser :: Text -> Text -> NonEmpty AttributeOperation -> UpdateUser
newUpdateUser Text
pIdentityStoreId_ Text
pUserId_ NonEmpty AttributeOperation
pOperations_ =
  UpdateUser'
    { $sel:identityStoreId:UpdateUser' :: Text
identityStoreId = Text
pIdentityStoreId_,
      $sel:userId:UpdateUser' :: Text
userId = Text
pUserId_,
      $sel:operations:UpdateUser' :: NonEmpty AttributeOperation
operations = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty AttributeOperation
pOperations_
    }

-- | The globally unique identifier for the identity store.
updateUser_identityStoreId :: Lens.Lens' UpdateUser Prelude.Text
updateUser_identityStoreId :: Lens' UpdateUser Text
updateUser_identityStoreId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Text
identityStoreId :: Text
$sel:identityStoreId:UpdateUser' :: UpdateUser -> Text
identityStoreId} -> Text
identityStoreId) (\s :: UpdateUser
s@UpdateUser' {} Text
a -> UpdateUser
s {$sel:identityStoreId:UpdateUser' :: Text
identityStoreId = Text
a} :: UpdateUser)

-- | The identifier for a user in the identity store.
updateUser_userId :: Lens.Lens' UpdateUser Prelude.Text
updateUser_userId :: Lens' UpdateUser Text
updateUser_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Text
userId :: Text
$sel:userId:UpdateUser' :: UpdateUser -> Text
userId} -> Text
userId) (\s :: UpdateUser
s@UpdateUser' {} Text
a -> UpdateUser
s {$sel:userId:UpdateUser' :: Text
userId = Text
a} :: UpdateUser)

-- | A list of @AttributeOperation@ objects to apply to the requested user.
-- These operations might add, replace, or remove an attribute.
updateUser_operations :: Lens.Lens' UpdateUser (Prelude.NonEmpty AttributeOperation)
updateUser_operations :: Lens' UpdateUser (NonEmpty AttributeOperation)
updateUser_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {NonEmpty AttributeOperation
operations :: NonEmpty AttributeOperation
$sel:operations:UpdateUser' :: UpdateUser -> NonEmpty AttributeOperation
operations} -> NonEmpty AttributeOperation
operations) (\s :: UpdateUser
s@UpdateUser' {} NonEmpty AttributeOperation
a -> UpdateUser
s {$sel:operations:UpdateUser' :: NonEmpty AttributeOperation
operations = NonEmpty AttributeOperation
a} :: UpdateUser) 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 UpdateUser where
  type AWSResponse UpdateUser = UpdateUserResponse
  request :: (Service -> Service) -> UpdateUser -> Request UpdateUser
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateUser)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateUserResponse
UpdateUserResponse'
            forall (f :: * -> *) a b. Functor 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 UpdateUser where
  hashWithSalt :: Int -> UpdateUser -> Int
hashWithSalt Int
_salt UpdateUser' {NonEmpty AttributeOperation
Text
operations :: NonEmpty AttributeOperation
userId :: Text
identityStoreId :: Text
$sel:operations:UpdateUser' :: UpdateUser -> NonEmpty AttributeOperation
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:identityStoreId:UpdateUser' :: UpdateUser -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityStoreId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty AttributeOperation
operations

instance Prelude.NFData UpdateUser where
  rnf :: UpdateUser -> ()
rnf UpdateUser' {NonEmpty AttributeOperation
Text
operations :: NonEmpty AttributeOperation
userId :: Text
identityStoreId :: Text
$sel:operations:UpdateUser' :: UpdateUser -> NonEmpty AttributeOperation
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:identityStoreId:UpdateUser' :: UpdateUser -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identityStoreId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AttributeOperation
operations

instance Data.ToHeaders UpdateUser where
  toHeaders :: UpdateUser -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSIdentityStore.UpdateUser" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateUser where
  toJSON :: UpdateUser -> Value
toJSON UpdateUser' {NonEmpty AttributeOperation
Text
operations :: NonEmpty AttributeOperation
userId :: Text
identityStoreId :: Text
$sel:operations:UpdateUser' :: UpdateUser -> NonEmpty AttributeOperation
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:identityStoreId:UpdateUser' :: UpdateUser -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"IdentityStoreId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
identityStoreId),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Operations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty AttributeOperation
operations)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateUserResponse' 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:
--
-- 'httpStatus', 'updateUserResponse_httpStatus' - The response's http status code.
newUpdateUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateUserResponse
newUpdateUserResponse :: Int -> UpdateUserResponse
newUpdateUserResponse Int
pHttpStatus_ =
  UpdateUserResponse' {$sel:httpStatus:UpdateUserResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData UpdateUserResponse where
  rnf :: UpdateUserResponse -> ()
rnf UpdateUserResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateUserResponse' :: UpdateUserResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus