{-# 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.MemoryDb.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)
--
-- Changes user password(s) and\/or access string.
module Amazonka.MemoryDb.UpdateUser
  ( -- * Creating a Request
    UpdateUser (..),
    newUpdateUser,

    -- * Request Lenses
    updateUser_accessString,
    updateUser_authenticationMode,
    updateUser_userName,

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

    -- * Response Lenses
    updateUserResponse_user,
    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.MemoryDb.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'
  { -- | Access permissions string used for this user.
    UpdateUser -> Maybe Text
accessString :: Prelude.Maybe Prelude.Text,
    -- | Denotes the user\'s authentication properties, such as whether it
    -- requires a password to authenticate.
    UpdateUser -> Maybe AuthenticationMode
authenticationMode :: Prelude.Maybe AuthenticationMode,
    -- | The name of the user
    UpdateUser -> Text
userName :: Prelude.Text
  }
  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:
--
-- 'accessString', 'updateUser_accessString' - Access permissions string used for this user.
--
-- 'authenticationMode', 'updateUser_authenticationMode' - Denotes the user\'s authentication properties, such as whether it
-- requires a password to authenticate.
--
-- 'userName', 'updateUser_userName' - The name of the user
newUpdateUser ::
  -- | 'userName'
  Prelude.Text ->
  UpdateUser
newUpdateUser :: Text -> UpdateUser
newUpdateUser Text
pUserName_ =
  UpdateUser'
    { $sel:accessString:UpdateUser' :: Maybe Text
accessString = forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationMode:UpdateUser' :: Maybe AuthenticationMode
authenticationMode = forall a. Maybe a
Prelude.Nothing,
      $sel:userName:UpdateUser' :: Text
userName = Text
pUserName_
    }

-- | Access permissions string used for this user.
updateUser_accessString :: Lens.Lens' UpdateUser (Prelude.Maybe Prelude.Text)
updateUser_accessString :: Lens' UpdateUser (Maybe Text)
updateUser_accessString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Maybe Text
accessString :: Maybe Text
$sel:accessString:UpdateUser' :: UpdateUser -> Maybe Text
accessString} -> Maybe Text
accessString) (\s :: UpdateUser
s@UpdateUser' {} Maybe Text
a -> UpdateUser
s {$sel:accessString:UpdateUser' :: Maybe Text
accessString = Maybe Text
a} :: UpdateUser)

-- | Denotes the user\'s authentication properties, such as whether it
-- requires a password to authenticate.
updateUser_authenticationMode :: Lens.Lens' UpdateUser (Prelude.Maybe AuthenticationMode)
updateUser_authenticationMode :: Lens' UpdateUser (Maybe AuthenticationMode)
updateUser_authenticationMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Maybe AuthenticationMode
authenticationMode :: Maybe AuthenticationMode
$sel:authenticationMode:UpdateUser' :: UpdateUser -> Maybe AuthenticationMode
authenticationMode} -> Maybe AuthenticationMode
authenticationMode) (\s :: UpdateUser
s@UpdateUser' {} Maybe AuthenticationMode
a -> UpdateUser
s {$sel:authenticationMode:UpdateUser' :: Maybe AuthenticationMode
authenticationMode = Maybe AuthenticationMode
a} :: UpdateUser)

-- | The name of the user
updateUser_userName :: Lens.Lens' UpdateUser Prelude.Text
updateUser_userName :: Lens' UpdateUser Text
updateUser_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Text
userName :: Text
$sel:userName:UpdateUser' :: UpdateUser -> Text
userName} -> Text
userName) (\s :: UpdateUser
s@UpdateUser' {} Text
a -> UpdateUser
s {$sel:userName:UpdateUser' :: Text
userName = Text
a} :: UpdateUser)

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 -> 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 User -> Int -> UpdateUserResponse
UpdateUserResponse'
            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
"User")
            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 UpdateUser where
  hashWithSalt :: Int -> UpdateUser -> Int
hashWithSalt Int
_salt UpdateUser' {Maybe Text
Maybe AuthenticationMode
Text
userName :: Text
authenticationMode :: Maybe AuthenticationMode
accessString :: Maybe Text
$sel:userName:UpdateUser' :: UpdateUser -> Text
$sel:authenticationMode:UpdateUser' :: UpdateUser -> Maybe AuthenticationMode
$sel:accessString:UpdateUser' :: UpdateUser -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accessString
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationMode
authenticationMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName

instance Prelude.NFData UpdateUser where
  rnf :: UpdateUser -> ()
rnf UpdateUser' {Maybe Text
Maybe AuthenticationMode
Text
userName :: Text
authenticationMode :: Maybe AuthenticationMode
accessString :: Maybe Text
$sel:userName:UpdateUser' :: UpdateUser -> Text
$sel:authenticationMode:UpdateUser' :: UpdateUser -> Maybe AuthenticationMode
$sel:accessString:UpdateUser' :: UpdateUser -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accessString
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationMode
authenticationMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userName

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
"AmazonMemoryDB.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' {Maybe Text
Maybe AuthenticationMode
Text
userName :: Text
authenticationMode :: Maybe AuthenticationMode
accessString :: Maybe Text
$sel:userName:UpdateUser' :: UpdateUser -> Text
$sel:authenticationMode:UpdateUser' :: UpdateUser -> Maybe AuthenticationMode
$sel:accessString:UpdateUser' :: UpdateUser -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccessString" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
accessString,
            (Key
"AuthenticationMode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AuthenticationMode
authenticationMode,
            forall a. a -> Maybe a
Prelude.Just (Key
"UserName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userName)
          ]
      )

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 updated user
    UpdateUserResponse -> Maybe User
user :: Prelude.Maybe User,
    -- | 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:
--
-- 'user', 'updateUserResponse_user' - The updated user
--
-- 'httpStatus', 'updateUserResponse_httpStatus' - The response's http status code.
newUpdateUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateUserResponse
newUpdateUserResponse :: Int -> UpdateUserResponse
newUpdateUserResponse Int
pHttpStatus_ =
  UpdateUserResponse'
    { $sel:user:UpdateUserResponse' :: Maybe User
user = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateUserResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The updated user
updateUserResponse_user :: Lens.Lens' UpdateUserResponse (Prelude.Maybe User)
updateUserResponse_user :: Lens' UpdateUserResponse (Maybe User)
updateUserResponse_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserResponse' {Maybe User
user :: Maybe User
$sel:user:UpdateUserResponse' :: UpdateUserResponse -> Maybe User
user} -> Maybe User
user) (\s :: UpdateUserResponse
s@UpdateUserResponse' {} Maybe User
a -> UpdateUserResponse
s {$sel:user:UpdateUserResponse' :: Maybe User
user = Maybe User
a} :: UpdateUserResponse)

-- | 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
Maybe User
httpStatus :: Int
user :: Maybe User
$sel:httpStatus:UpdateUserResponse' :: UpdateUserResponse -> Int
$sel:user:UpdateUserResponse' :: UpdateUserResponse -> Maybe User
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe User
user
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus