{-# 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.UpdateRoutingProfileDefaultOutboundQueue
-- 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 default outbound queue of a routing profile.
module Amazonka.Connect.UpdateRoutingProfileDefaultOutboundQueue
  ( -- * Creating a Request
    UpdateRoutingProfileDefaultOutboundQueue (..),
    newUpdateRoutingProfileDefaultOutboundQueue,

    -- * Request Lenses
    updateRoutingProfileDefaultOutboundQueue_instanceId,
    updateRoutingProfileDefaultOutboundQueue_routingProfileId,
    updateRoutingProfileDefaultOutboundQueue_defaultOutboundQueueId,

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

-- |
-- Create a value of 'UpdateRoutingProfileDefaultOutboundQueue' 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:
--
-- 'instanceId', 'updateRoutingProfileDefaultOutboundQueue_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'routingProfileId', 'updateRoutingProfileDefaultOutboundQueue_routingProfileId' - The identifier of the routing profile.
--
-- 'defaultOutboundQueueId', 'updateRoutingProfileDefaultOutboundQueue_defaultOutboundQueueId' - The identifier for the default outbound queue.
newUpdateRoutingProfileDefaultOutboundQueue ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'routingProfileId'
  Prelude.Text ->
  -- | 'defaultOutboundQueueId'
  Prelude.Text ->
  UpdateRoutingProfileDefaultOutboundQueue
newUpdateRoutingProfileDefaultOutboundQueue :: Text -> Text -> Text -> UpdateRoutingProfileDefaultOutboundQueue
newUpdateRoutingProfileDefaultOutboundQueue
  Text
pInstanceId_
  Text
pRoutingProfileId_
  Text
pDefaultOutboundQueueId_ =
    UpdateRoutingProfileDefaultOutboundQueue'
      { $sel:instanceId:UpdateRoutingProfileDefaultOutboundQueue' :: Text
instanceId =
          Text
pInstanceId_,
        $sel:routingProfileId:UpdateRoutingProfileDefaultOutboundQueue' :: Text
routingProfileId =
          Text
pRoutingProfileId_,
        $sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: Text
defaultOutboundQueueId =
          Text
pDefaultOutboundQueueId_
      }

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

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

-- | The identifier for the default outbound queue.
updateRoutingProfileDefaultOutboundQueue_defaultOutboundQueueId :: Lens.Lens' UpdateRoutingProfileDefaultOutboundQueue Prelude.Text
updateRoutingProfileDefaultOutboundQueue_defaultOutboundQueueId :: Lens' UpdateRoutingProfileDefaultOutboundQueue Text
updateRoutingProfileDefaultOutboundQueue_defaultOutboundQueueId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoutingProfileDefaultOutboundQueue' {Text
defaultOutboundQueueId :: Text
$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
defaultOutboundQueueId} -> Text
defaultOutboundQueueId) (\s :: UpdateRoutingProfileDefaultOutboundQueue
s@UpdateRoutingProfileDefaultOutboundQueue' {} Text
a -> UpdateRoutingProfileDefaultOutboundQueue
s {$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: Text
defaultOutboundQueueId = Text
a} :: UpdateRoutingProfileDefaultOutboundQueue)

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

instance
  Prelude.Hashable
    UpdateRoutingProfileDefaultOutboundQueue
  where
  hashWithSalt :: Int -> UpdateRoutingProfileDefaultOutboundQueue -> Int
hashWithSalt
    Int
_salt
    UpdateRoutingProfileDefaultOutboundQueue' {Text
defaultOutboundQueueId :: Text
routingProfileId :: Text
instanceId :: Text
$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:routingProfileId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:instanceId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routingProfileId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
defaultOutboundQueueId

instance
  Prelude.NFData
    UpdateRoutingProfileDefaultOutboundQueue
  where
  rnf :: UpdateRoutingProfileDefaultOutboundQueue -> ()
rnf UpdateRoutingProfileDefaultOutboundQueue' {Text
defaultOutboundQueueId :: Text
routingProfileId :: Text
instanceId :: Text
$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:routingProfileId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:instanceId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
defaultOutboundQueueId

instance
  Data.ToHeaders
    UpdateRoutingProfileDefaultOutboundQueue
  where
  toHeaders :: UpdateRoutingProfileDefaultOutboundQueue -> [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
    UpdateRoutingProfileDefaultOutboundQueue
  where
  toJSON :: UpdateRoutingProfileDefaultOutboundQueue -> Value
toJSON UpdateRoutingProfileDefaultOutboundQueue' {Text
defaultOutboundQueueId :: Text
routingProfileId :: Text
instanceId :: Text
$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:routingProfileId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:instanceId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"DefaultOutboundQueueId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
defaultOutboundQueueId
              )
          ]
      )

instance
  Data.ToPath
    UpdateRoutingProfileDefaultOutboundQueue
  where
  toPath :: UpdateRoutingProfileDefaultOutboundQueue -> ByteString
toPath UpdateRoutingProfileDefaultOutboundQueue' {Text
defaultOutboundQueueId :: Text
routingProfileId :: Text
instanceId :: Text
$sel:defaultOutboundQueueId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:routingProfileId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
$sel:instanceId:UpdateRoutingProfileDefaultOutboundQueue' :: UpdateRoutingProfileDefaultOutboundQueue -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/routing-profiles/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
routingProfileId,
        ByteString
"/default-outbound-queue"
      ]

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

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

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

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