{-# 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.UpdateUserRoutingProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Assigns the specified routing profile to the specified user.
module Amazonka.Connect.UpdateUserRoutingProfile
  ( -- * Creating a Request
    UpdateUserRoutingProfile (..),
    newUpdateUserRoutingProfile,

    -- * Request Lenses
    updateUserRoutingProfile_routingProfileId,
    updateUserRoutingProfile_userId,
    updateUserRoutingProfile_instanceId,

    -- * Destructuring the Response
    UpdateUserRoutingProfileResponse (..),
    newUpdateUserRoutingProfileResponse,
  )
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:/ 'newUpdateUserRoutingProfile' smart constructor.
data UpdateUserRoutingProfile = UpdateUserRoutingProfile'
  { -- | The identifier of the routing profile for the user.
    UpdateUserRoutingProfile -> Text
routingProfileId :: Prelude.Text,
    -- | The identifier of the user account.
    UpdateUserRoutingProfile -> Text
userId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    UpdateUserRoutingProfile -> Text
instanceId :: Prelude.Text
  }
  deriving (UpdateUserRoutingProfile -> UpdateUserRoutingProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserRoutingProfile -> UpdateUserRoutingProfile -> Bool
$c/= :: UpdateUserRoutingProfile -> UpdateUserRoutingProfile -> Bool
== :: UpdateUserRoutingProfile -> UpdateUserRoutingProfile -> Bool
$c== :: UpdateUserRoutingProfile -> UpdateUserRoutingProfile -> Bool
Prelude.Eq, ReadPrec [UpdateUserRoutingProfile]
ReadPrec UpdateUserRoutingProfile
Int -> ReadS UpdateUserRoutingProfile
ReadS [UpdateUserRoutingProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserRoutingProfile]
$creadListPrec :: ReadPrec [UpdateUserRoutingProfile]
readPrec :: ReadPrec UpdateUserRoutingProfile
$creadPrec :: ReadPrec UpdateUserRoutingProfile
readList :: ReadS [UpdateUserRoutingProfile]
$creadList :: ReadS [UpdateUserRoutingProfile]
readsPrec :: Int -> ReadS UpdateUserRoutingProfile
$creadsPrec :: Int -> ReadS UpdateUserRoutingProfile
Prelude.Read, Int -> UpdateUserRoutingProfile -> ShowS
[UpdateUserRoutingProfile] -> ShowS
UpdateUserRoutingProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserRoutingProfile] -> ShowS
$cshowList :: [UpdateUserRoutingProfile] -> ShowS
show :: UpdateUserRoutingProfile -> String
$cshow :: UpdateUserRoutingProfile -> String
showsPrec :: Int -> UpdateUserRoutingProfile -> ShowS
$cshowsPrec :: Int -> UpdateUserRoutingProfile -> ShowS
Prelude.Show, forall x.
Rep UpdateUserRoutingProfile x -> UpdateUserRoutingProfile
forall x.
UpdateUserRoutingProfile -> Rep UpdateUserRoutingProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateUserRoutingProfile x -> UpdateUserRoutingProfile
$cfrom :: forall x.
UpdateUserRoutingProfile -> Rep UpdateUserRoutingProfile x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUserRoutingProfile' 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:
--
-- 'routingProfileId', 'updateUserRoutingProfile_routingProfileId' - The identifier of the routing profile for the user.
--
-- 'userId', 'updateUserRoutingProfile_userId' - The identifier of the user account.
--
-- 'instanceId', 'updateUserRoutingProfile_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newUpdateUserRoutingProfile ::
  -- | 'routingProfileId'
  Prelude.Text ->
  -- | 'userId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  UpdateUserRoutingProfile
newUpdateUserRoutingProfile :: Text -> Text -> Text -> UpdateUserRoutingProfile
newUpdateUserRoutingProfile
  Text
pRoutingProfileId_
  Text
pUserId_
  Text
pInstanceId_ =
    UpdateUserRoutingProfile'
      { $sel:routingProfileId:UpdateUserRoutingProfile' :: Text
routingProfileId =
          Text
pRoutingProfileId_,
        $sel:userId:UpdateUserRoutingProfile' :: Text
userId = Text
pUserId_,
        $sel:instanceId:UpdateUserRoutingProfile' :: Text
instanceId = Text
pInstanceId_
      }

-- | The identifier of the routing profile for the user.
updateUserRoutingProfile_routingProfileId :: Lens.Lens' UpdateUserRoutingProfile Prelude.Text
updateUserRoutingProfile_routingProfileId :: Lens' UpdateUserRoutingProfile Text
updateUserRoutingProfile_routingProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserRoutingProfile' {Text
routingProfileId :: Text
$sel:routingProfileId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
routingProfileId} -> Text
routingProfileId) (\s :: UpdateUserRoutingProfile
s@UpdateUserRoutingProfile' {} Text
a -> UpdateUserRoutingProfile
s {$sel:routingProfileId:UpdateUserRoutingProfile' :: Text
routingProfileId = Text
a} :: UpdateUserRoutingProfile)

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

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

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

instance Prelude.Hashable UpdateUserRoutingProfile where
  hashWithSalt :: Int -> UpdateUserRoutingProfile -> Int
hashWithSalt Int
_salt UpdateUserRoutingProfile' {Text
instanceId :: Text
userId :: Text
routingProfileId :: Text
$sel:instanceId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:userId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:routingProfileId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routingProfileId
      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 UpdateUserRoutingProfile where
  rnf :: UpdateUserRoutingProfile -> ()
rnf UpdateUserRoutingProfile' {Text
instanceId :: Text
userId :: Text
routingProfileId :: Text
$sel:instanceId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:userId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:routingProfileId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
routingProfileId
      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 UpdateUserRoutingProfile where
  toHeaders :: UpdateUserRoutingProfile -> [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 UpdateUserRoutingProfile where
  toJSON :: UpdateUserRoutingProfile -> Value
toJSON UpdateUserRoutingProfile' {Text
instanceId :: Text
userId :: Text
routingProfileId :: Text
$sel:instanceId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:userId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:routingProfileId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"RoutingProfileId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
routingProfileId)
          ]
      )

instance Data.ToPath UpdateUserRoutingProfile where
  toPath :: UpdateUserRoutingProfile -> ByteString
toPath UpdateUserRoutingProfile' {Text
instanceId :: Text
userId :: Text
routingProfileId :: Text
$sel:instanceId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:userId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
$sel:routingProfileId:UpdateUserRoutingProfile' :: UpdateUserRoutingProfile -> Text
..} =
    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
"/routing-profile"
      ]

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

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

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

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