{-# 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.Connect.UpdateUserPhoneConfig
-- 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 the phone configuration settings for the specified user.
module Amazonka.Connect.UpdateUserPhoneConfig
  ( -- * Creating a Request
    UpdateUserPhoneConfig (..),
    newUpdateUserPhoneConfig,

    -- * Request Lenses
    updateUserPhoneConfig_phoneConfig,
    updateUserPhoneConfig_userId,
    updateUserPhoneConfig_instanceId,

    -- * Destructuring the Response
    UpdateUserPhoneConfigResponse (..),
    newUpdateUserPhoneConfigResponse,
  )
where

import Amazonka.Connect.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:/ 'newUpdateUserPhoneConfig' smart constructor.
data UpdateUserPhoneConfig = UpdateUserPhoneConfig'
  { -- | Information about phone configuration settings for the user.
    UpdateUserPhoneConfig -> UserPhoneConfig
phoneConfig :: UserPhoneConfig,
    -- | The identifier of the user account.
    UpdateUserPhoneConfig -> Text
userId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    UpdateUserPhoneConfig -> Text
instanceId :: Prelude.Text
  }
  deriving (UpdateUserPhoneConfig -> UpdateUserPhoneConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserPhoneConfig -> UpdateUserPhoneConfig -> Bool
$c/= :: UpdateUserPhoneConfig -> UpdateUserPhoneConfig -> Bool
== :: UpdateUserPhoneConfig -> UpdateUserPhoneConfig -> Bool
$c== :: UpdateUserPhoneConfig -> UpdateUserPhoneConfig -> Bool
Prelude.Eq, ReadPrec [UpdateUserPhoneConfig]
ReadPrec UpdateUserPhoneConfig
Int -> ReadS UpdateUserPhoneConfig
ReadS [UpdateUserPhoneConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserPhoneConfig]
$creadListPrec :: ReadPrec [UpdateUserPhoneConfig]
readPrec :: ReadPrec UpdateUserPhoneConfig
$creadPrec :: ReadPrec UpdateUserPhoneConfig
readList :: ReadS [UpdateUserPhoneConfig]
$creadList :: ReadS [UpdateUserPhoneConfig]
readsPrec :: Int -> ReadS UpdateUserPhoneConfig
$creadsPrec :: Int -> ReadS UpdateUserPhoneConfig
Prelude.Read, Int -> UpdateUserPhoneConfig -> ShowS
[UpdateUserPhoneConfig] -> ShowS
UpdateUserPhoneConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserPhoneConfig] -> ShowS
$cshowList :: [UpdateUserPhoneConfig] -> ShowS
show :: UpdateUserPhoneConfig -> String
$cshow :: UpdateUserPhoneConfig -> String
showsPrec :: Int -> UpdateUserPhoneConfig -> ShowS
$cshowsPrec :: Int -> UpdateUserPhoneConfig -> ShowS
Prelude.Show, forall x. Rep UpdateUserPhoneConfig x -> UpdateUserPhoneConfig
forall x. UpdateUserPhoneConfig -> Rep UpdateUserPhoneConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUserPhoneConfig x -> UpdateUserPhoneConfig
$cfrom :: forall x. UpdateUserPhoneConfig -> Rep UpdateUserPhoneConfig x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUserPhoneConfig' 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:
--
-- 'phoneConfig', 'updateUserPhoneConfig_phoneConfig' - Information about phone configuration settings for the user.
--
-- 'userId', 'updateUserPhoneConfig_userId' - The identifier of the user account.
--
-- 'instanceId', 'updateUserPhoneConfig_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newUpdateUserPhoneConfig ::
  -- | 'phoneConfig'
  UserPhoneConfig ->
  -- | 'userId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  UpdateUserPhoneConfig
newUpdateUserPhoneConfig :: UserPhoneConfig -> Text -> Text -> UpdateUserPhoneConfig
newUpdateUserPhoneConfig
  UserPhoneConfig
pPhoneConfig_
  Text
pUserId_
  Text
pInstanceId_ =
    UpdateUserPhoneConfig'
      { $sel:phoneConfig:UpdateUserPhoneConfig' :: UserPhoneConfig
phoneConfig = UserPhoneConfig
pPhoneConfig_,
        $sel:userId:UpdateUserPhoneConfig' :: Text
userId = Text
pUserId_,
        $sel:instanceId:UpdateUserPhoneConfig' :: Text
instanceId = Text
pInstanceId_
      }

-- | Information about phone configuration settings for the user.
updateUserPhoneConfig_phoneConfig :: Lens.Lens' UpdateUserPhoneConfig UserPhoneConfig
updateUserPhoneConfig_phoneConfig :: Lens' UpdateUserPhoneConfig UserPhoneConfig
updateUserPhoneConfig_phoneConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPhoneConfig' {UserPhoneConfig
phoneConfig :: UserPhoneConfig
$sel:phoneConfig:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> UserPhoneConfig
phoneConfig} -> UserPhoneConfig
phoneConfig) (\s :: UpdateUserPhoneConfig
s@UpdateUserPhoneConfig' {} UserPhoneConfig
a -> UpdateUserPhoneConfig
s {$sel:phoneConfig:UpdateUserPhoneConfig' :: UserPhoneConfig
phoneConfig = UserPhoneConfig
a} :: UpdateUserPhoneConfig)

-- | The identifier of the user account.
updateUserPhoneConfig_userId :: Lens.Lens' UpdateUserPhoneConfig Prelude.Text
updateUserPhoneConfig_userId :: Lens' UpdateUserPhoneConfig Text
updateUserPhoneConfig_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPhoneConfig' {Text
userId :: Text
$sel:userId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
userId} -> Text
userId) (\s :: UpdateUserPhoneConfig
s@UpdateUserPhoneConfig' {} Text
a -> UpdateUserPhoneConfig
s {$sel:userId:UpdateUserPhoneConfig' :: Text
userId = Text
a} :: UpdateUserPhoneConfig)

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
updateUserPhoneConfig_instanceId :: Lens.Lens' UpdateUserPhoneConfig Prelude.Text
updateUserPhoneConfig_instanceId :: Lens' UpdateUserPhoneConfig Text
updateUserPhoneConfig_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPhoneConfig' {Text
instanceId :: Text
$sel:instanceId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
instanceId} -> Text
instanceId) (\s :: UpdateUserPhoneConfig
s@UpdateUserPhoneConfig' {} Text
a -> UpdateUserPhoneConfig
s {$sel:instanceId:UpdateUserPhoneConfig' :: Text
instanceId = Text
a} :: UpdateUserPhoneConfig)

instance Core.AWSRequest UpdateUserPhoneConfig where
  type
    AWSResponse UpdateUserPhoneConfig =
      UpdateUserPhoneConfigResponse
  request :: (Service -> Service)
-> UpdateUserPhoneConfig -> Request UpdateUserPhoneConfig
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 UpdateUserPhoneConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateUserPhoneConfig)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateUserPhoneConfigResponse
UpdateUserPhoneConfigResponse'

instance Prelude.Hashable UpdateUserPhoneConfig where
  hashWithSalt :: Int -> UpdateUserPhoneConfig -> Int
hashWithSalt Int
_salt UpdateUserPhoneConfig' {Text
UserPhoneConfig
instanceId :: Text
userId :: Text
phoneConfig :: UserPhoneConfig
$sel:instanceId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:userId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:phoneConfig:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> UserPhoneConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UserPhoneConfig
phoneConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData UpdateUserPhoneConfig where
  rnf :: UpdateUserPhoneConfig -> ()
rnf UpdateUserPhoneConfig' {Text
UserPhoneConfig
instanceId :: Text
userId :: Text
phoneConfig :: UserPhoneConfig
$sel:instanceId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:userId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:phoneConfig:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> UserPhoneConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf UserPhoneConfig
phoneConfig
      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 Text
instanceId

instance Data.ToHeaders UpdateUserPhoneConfig where
  toHeaders :: UpdateUserPhoneConfig -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateUserPhoneConfig where
  toJSON :: UpdateUserPhoneConfig -> Value
toJSON UpdateUserPhoneConfig' {Text
UserPhoneConfig
instanceId :: Text
userId :: Text
phoneConfig :: UserPhoneConfig
$sel:instanceId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:userId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:phoneConfig:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> UserPhoneConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"PhoneConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= UserPhoneConfig
phoneConfig)]
      )

instance Data.ToPath UpdateUserPhoneConfig where
  toPath :: UpdateUserPhoneConfig -> ByteString
toPath UpdateUserPhoneConfig' {Text
UserPhoneConfig
instanceId :: Text
userId :: Text
phoneConfig :: UserPhoneConfig
$sel:instanceId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:userId:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> Text
$sel:phoneConfig:UpdateUserPhoneConfig' :: UpdateUserPhoneConfig -> UserPhoneConfig
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/users/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
userId,
        ByteString
"/phone-config"
      ]

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

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

-- |
-- Create a value of 'UpdateUserPhoneConfigResponse' 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.
newUpdateUserPhoneConfigResponse ::
  UpdateUserPhoneConfigResponse
newUpdateUserPhoneConfigResponse :: UpdateUserPhoneConfigResponse
newUpdateUserPhoneConfigResponse =
  UpdateUserPhoneConfigResponse
UpdateUserPhoneConfigResponse'

instance Prelude.NFData UpdateUserPhoneConfigResponse where
  rnf :: UpdateUserPhoneConfigResponse -> ()
rnf UpdateUserPhoneConfigResponse
_ = ()