{-# 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.Chime.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)
--
-- Updates user details for a specified user ID. Currently, only
-- @LicenseType@ updates are supported for this action.
module Amazonka.Chime.UpdateUser
  ( -- * Creating a Request
    UpdateUser (..),
    newUpdateUser,

    -- * Request Lenses
    updateUser_alexaForBusinessMetadata,
    updateUser_licenseType,
    updateUser_userType,
    updateUser_accountId,
    updateUser_userId,

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

    -- * Response Lenses
    updateUserResponse_user,
    updateUserResponse_httpStatus,
  )
where

import Amazonka.Chime.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:/ 'newUpdateUser' smart constructor.
data UpdateUser = UpdateUser'
  { -- | The Alexa for Business metadata.
    UpdateUser -> Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata :: Prelude.Maybe AlexaForBusinessMetadata,
    -- | The user license type to update. This must be a supported license type
    -- for the Amazon Chime account that the user belongs to.
    UpdateUser -> Maybe License
licenseType :: Prelude.Maybe License,
    -- | The user type.
    UpdateUser -> Maybe UserType
userType :: Prelude.Maybe UserType,
    -- | The Amazon Chime account ID.
    UpdateUser -> Text
accountId :: Prelude.Text,
    -- | The user ID.
    UpdateUser -> Text
userId :: 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, 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:
--
-- 'alexaForBusinessMetadata', 'updateUser_alexaForBusinessMetadata' - The Alexa for Business metadata.
--
-- 'licenseType', 'updateUser_licenseType' - The user license type to update. This must be a supported license type
-- for the Amazon Chime account that the user belongs to.
--
-- 'userType', 'updateUser_userType' - The user type.
--
-- 'accountId', 'updateUser_accountId' - The Amazon Chime account ID.
--
-- 'userId', 'updateUser_userId' - The user ID.
newUpdateUser ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'userId'
  Prelude.Text ->
  UpdateUser
newUpdateUser :: Text -> Text -> UpdateUser
newUpdateUser Text
pAccountId_ Text
pUserId_ =
  UpdateUser'
    { $sel:alexaForBusinessMetadata:UpdateUser' :: Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata =
        forall a. Maybe a
Prelude.Nothing,
      $sel:licenseType:UpdateUser' :: Maybe License
licenseType = forall a. Maybe a
Prelude.Nothing,
      $sel:userType:UpdateUser' :: Maybe UserType
userType = forall a. Maybe a
Prelude.Nothing,
      $sel:accountId:UpdateUser' :: Text
accountId = Text
pAccountId_,
      $sel:userId:UpdateUser' :: Text
userId = Text
pUserId_
    }

-- | The Alexa for Business metadata.
updateUser_alexaForBusinessMetadata :: Lens.Lens' UpdateUser (Prelude.Maybe AlexaForBusinessMetadata)
updateUser_alexaForBusinessMetadata :: Lens' UpdateUser (Maybe AlexaForBusinessMetadata)
updateUser_alexaForBusinessMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata :: Maybe AlexaForBusinessMetadata
$sel:alexaForBusinessMetadata:UpdateUser' :: UpdateUser -> Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata} -> Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata) (\s :: UpdateUser
s@UpdateUser' {} Maybe AlexaForBusinessMetadata
a -> UpdateUser
s {$sel:alexaForBusinessMetadata:UpdateUser' :: Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata = Maybe AlexaForBusinessMetadata
a} :: UpdateUser)

-- | The user license type to update. This must be a supported license type
-- for the Amazon Chime account that the user belongs to.
updateUser_licenseType :: Lens.Lens' UpdateUser (Prelude.Maybe License)
updateUser_licenseType :: Lens' UpdateUser (Maybe License)
updateUser_licenseType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Maybe License
licenseType :: Maybe License
$sel:licenseType:UpdateUser' :: UpdateUser -> Maybe License
licenseType} -> Maybe License
licenseType) (\s :: UpdateUser
s@UpdateUser' {} Maybe License
a -> UpdateUser
s {$sel:licenseType:UpdateUser' :: Maybe License
licenseType = Maybe License
a} :: UpdateUser)

-- | The user type.
updateUser_userType :: Lens.Lens' UpdateUser (Prelude.Maybe UserType)
updateUser_userType :: Lens' UpdateUser (Maybe UserType)
updateUser_userType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Maybe UserType
userType :: Maybe UserType
$sel:userType:UpdateUser' :: UpdateUser -> Maybe UserType
userType} -> Maybe UserType
userType) (\s :: UpdateUser
s@UpdateUser' {} Maybe UserType
a -> UpdateUser
s {$sel:userType:UpdateUser' :: Maybe UserType
userType = Maybe UserType
a} :: UpdateUser)

-- | The Amazon Chime account ID.
updateUser_accountId :: Lens.Lens' UpdateUser Prelude.Text
updateUser_accountId :: Lens' UpdateUser Text
updateUser_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUser' {Text
accountId :: Text
$sel:accountId:UpdateUser' :: UpdateUser -> Text
accountId} -> Text
accountId) (\s :: UpdateUser
s@UpdateUser' {} Text
a -> UpdateUser
s {$sel:accountId:UpdateUser' :: Text
accountId = Text
a} :: UpdateUser)

-- | The user ID.
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)

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 AlexaForBusinessMetadata
Maybe License
Maybe UserType
Text
userId :: Text
accountId :: Text
userType :: Maybe UserType
licenseType :: Maybe License
alexaForBusinessMetadata :: Maybe AlexaForBusinessMetadata
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:accountId:UpdateUser' :: UpdateUser -> Text
$sel:userType:UpdateUser' :: UpdateUser -> Maybe UserType
$sel:licenseType:UpdateUser' :: UpdateUser -> Maybe License
$sel:alexaForBusinessMetadata:UpdateUser' :: UpdateUser -> Maybe AlexaForBusinessMetadata
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe License
licenseType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserType
userType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userId

instance Prelude.NFData UpdateUser where
  rnf :: UpdateUser -> ()
rnf UpdateUser' {Maybe AlexaForBusinessMetadata
Maybe License
Maybe UserType
Text
userId :: Text
accountId :: Text
userType :: Maybe UserType
licenseType :: Maybe License
alexaForBusinessMetadata :: Maybe AlexaForBusinessMetadata
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:accountId:UpdateUser' :: UpdateUser -> Text
$sel:userType:UpdateUser' :: UpdateUser -> Maybe UserType
$sel:licenseType:UpdateUser' :: UpdateUser -> Maybe License
$sel:alexaForBusinessMetadata:UpdateUser' :: UpdateUser -> Maybe AlexaForBusinessMetadata
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlexaForBusinessMetadata
alexaForBusinessMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe License
licenseType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserType
userType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userId

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

instance Data.ToJSON UpdateUser where
  toJSON :: UpdateUser -> Value
toJSON UpdateUser' {Maybe AlexaForBusinessMetadata
Maybe License
Maybe UserType
Text
userId :: Text
accountId :: Text
userType :: Maybe UserType
licenseType :: Maybe License
alexaForBusinessMetadata :: Maybe AlexaForBusinessMetadata
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:accountId:UpdateUser' :: UpdateUser -> Text
$sel:userType:UpdateUser' :: UpdateUser -> Maybe UserType
$sel:licenseType:UpdateUser' :: UpdateUser -> Maybe License
$sel:alexaForBusinessMetadata:UpdateUser' :: UpdateUser -> Maybe AlexaForBusinessMetadata
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AlexaForBusinessMetadata" 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 AlexaForBusinessMetadata
alexaForBusinessMetadata,
            (Key
"LicenseType" 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 License
licenseType,
            (Key
"UserType" 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 UserType
userType
          ]
      )

instance Data.ToPath UpdateUser where
  toPath :: UpdateUser -> ByteString
toPath UpdateUser' {Maybe AlexaForBusinessMetadata
Maybe License
Maybe UserType
Text
userId :: Text
accountId :: Text
userType :: Maybe UserType
licenseType :: Maybe License
alexaForBusinessMetadata :: Maybe AlexaForBusinessMetadata
$sel:userId:UpdateUser' :: UpdateUser -> Text
$sel:accountId:UpdateUser' :: UpdateUser -> Text
$sel:userType:UpdateUser' :: UpdateUser -> Maybe UserType
$sel:licenseType:UpdateUser' :: UpdateUser -> Maybe License
$sel:alexaForBusinessMetadata:UpdateUser' :: UpdateUser -> Maybe AlexaForBusinessMetadata
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/accounts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId,
        ByteString
"/users/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
userId
      ]

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 details.
    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, 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 details.
--
-- '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 details.
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