{-# 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.AssociateRoutingProfileQueues
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates a set of queues with a routing profile.
module Amazonka.Connect.AssociateRoutingProfileQueues
  ( -- * Creating a Request
    AssociateRoutingProfileQueues (..),
    newAssociateRoutingProfileQueues,

    -- * Request Lenses
    associateRoutingProfileQueues_instanceId,
    associateRoutingProfileQueues_routingProfileId,
    associateRoutingProfileQueues_queueConfigs,

    -- * Destructuring the Response
    AssociateRoutingProfileQueuesResponse (..),
    newAssociateRoutingProfileQueuesResponse,
  )
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:/ 'newAssociateRoutingProfileQueues' smart constructor.
data AssociateRoutingProfileQueues = AssociateRoutingProfileQueues'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    AssociateRoutingProfileQueues -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the routing profile.
    AssociateRoutingProfileQueues -> Text
routingProfileId :: Prelude.Text,
    -- | The queues to associate with this routing profile.
    AssociateRoutingProfileQueues -> NonEmpty RoutingProfileQueueConfig
queueConfigs :: Prelude.NonEmpty RoutingProfileQueueConfig
  }
  deriving (AssociateRoutingProfileQueues
-> AssociateRoutingProfileQueues -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateRoutingProfileQueues
-> AssociateRoutingProfileQueues -> Bool
$c/= :: AssociateRoutingProfileQueues
-> AssociateRoutingProfileQueues -> Bool
== :: AssociateRoutingProfileQueues
-> AssociateRoutingProfileQueues -> Bool
$c== :: AssociateRoutingProfileQueues
-> AssociateRoutingProfileQueues -> Bool
Prelude.Eq, ReadPrec [AssociateRoutingProfileQueues]
ReadPrec AssociateRoutingProfileQueues
Int -> ReadS AssociateRoutingProfileQueues
ReadS [AssociateRoutingProfileQueues]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateRoutingProfileQueues]
$creadListPrec :: ReadPrec [AssociateRoutingProfileQueues]
readPrec :: ReadPrec AssociateRoutingProfileQueues
$creadPrec :: ReadPrec AssociateRoutingProfileQueues
readList :: ReadS [AssociateRoutingProfileQueues]
$creadList :: ReadS [AssociateRoutingProfileQueues]
readsPrec :: Int -> ReadS AssociateRoutingProfileQueues
$creadsPrec :: Int -> ReadS AssociateRoutingProfileQueues
Prelude.Read, Int -> AssociateRoutingProfileQueues -> ShowS
[AssociateRoutingProfileQueues] -> ShowS
AssociateRoutingProfileQueues -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateRoutingProfileQueues] -> ShowS
$cshowList :: [AssociateRoutingProfileQueues] -> ShowS
show :: AssociateRoutingProfileQueues -> String
$cshow :: AssociateRoutingProfileQueues -> String
showsPrec :: Int -> AssociateRoutingProfileQueues -> ShowS
$cshowsPrec :: Int -> AssociateRoutingProfileQueues -> ShowS
Prelude.Show, forall x.
Rep AssociateRoutingProfileQueues x
-> AssociateRoutingProfileQueues
forall x.
AssociateRoutingProfileQueues
-> Rep AssociateRoutingProfileQueues x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateRoutingProfileQueues x
-> AssociateRoutingProfileQueues
$cfrom :: forall x.
AssociateRoutingProfileQueues
-> Rep AssociateRoutingProfileQueues x
Prelude.Generic)

-- |
-- Create a value of 'AssociateRoutingProfileQueues' 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', 'associateRoutingProfileQueues_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'routingProfileId', 'associateRoutingProfileQueues_routingProfileId' - The identifier of the routing profile.
--
-- 'queueConfigs', 'associateRoutingProfileQueues_queueConfigs' - The queues to associate with this routing profile.
newAssociateRoutingProfileQueues ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'routingProfileId'
  Prelude.Text ->
  -- | 'queueConfigs'
  Prelude.NonEmpty RoutingProfileQueueConfig ->
  AssociateRoutingProfileQueues
newAssociateRoutingProfileQueues :: Text
-> Text
-> NonEmpty RoutingProfileQueueConfig
-> AssociateRoutingProfileQueues
newAssociateRoutingProfileQueues
  Text
pInstanceId_
  Text
pRoutingProfileId_
  NonEmpty RoutingProfileQueueConfig
pQueueConfigs_ =
    AssociateRoutingProfileQueues'
      { $sel:instanceId:AssociateRoutingProfileQueues' :: Text
instanceId =
          Text
pInstanceId_,
        $sel:routingProfileId:AssociateRoutingProfileQueues' :: Text
routingProfileId = Text
pRoutingProfileId_,
        $sel:queueConfigs:AssociateRoutingProfileQueues' :: NonEmpty RoutingProfileQueueConfig
queueConfigs =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty RoutingProfileQueueConfig
pQueueConfigs_
      }

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

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

-- | The queues to associate with this routing profile.
associateRoutingProfileQueues_queueConfigs :: Lens.Lens' AssociateRoutingProfileQueues (Prelude.NonEmpty RoutingProfileQueueConfig)
associateRoutingProfileQueues_queueConfigs :: Lens'
  AssociateRoutingProfileQueues (NonEmpty RoutingProfileQueueConfig)
associateRoutingProfileQueues_queueConfigs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateRoutingProfileQueues' {NonEmpty RoutingProfileQueueConfig
queueConfigs :: NonEmpty RoutingProfileQueueConfig
$sel:queueConfigs:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> NonEmpty RoutingProfileQueueConfig
queueConfigs} -> NonEmpty RoutingProfileQueueConfig
queueConfigs) (\s :: AssociateRoutingProfileQueues
s@AssociateRoutingProfileQueues' {} NonEmpty RoutingProfileQueueConfig
a -> AssociateRoutingProfileQueues
s {$sel:queueConfigs:AssociateRoutingProfileQueues' :: NonEmpty RoutingProfileQueueConfig
queueConfigs = NonEmpty RoutingProfileQueueConfig
a} :: AssociateRoutingProfileQueues) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.Hashable
    AssociateRoutingProfileQueues
  where
  hashWithSalt :: Int -> AssociateRoutingProfileQueues -> Int
hashWithSalt Int
_salt AssociateRoutingProfileQueues' {NonEmpty RoutingProfileQueueConfig
Text
queueConfigs :: NonEmpty RoutingProfileQueueConfig
routingProfileId :: Text
instanceId :: Text
$sel:queueConfigs:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> NonEmpty RoutingProfileQueueConfig
$sel:routingProfileId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> Text
$sel:instanceId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> 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` NonEmpty RoutingProfileQueueConfig
queueConfigs

instance Prelude.NFData AssociateRoutingProfileQueues where
  rnf :: AssociateRoutingProfileQueues -> ()
rnf AssociateRoutingProfileQueues' {NonEmpty RoutingProfileQueueConfig
Text
queueConfigs :: NonEmpty RoutingProfileQueueConfig
routingProfileId :: Text
instanceId :: Text
$sel:queueConfigs:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> NonEmpty RoutingProfileQueueConfig
$sel:routingProfileId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> Text
$sel:instanceId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> 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 NonEmpty RoutingProfileQueueConfig
queueConfigs

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

instance Data.ToPath AssociateRoutingProfileQueues where
  toPath :: AssociateRoutingProfileQueues -> ByteString
toPath AssociateRoutingProfileQueues' {NonEmpty RoutingProfileQueueConfig
Text
queueConfigs :: NonEmpty RoutingProfileQueueConfig
routingProfileId :: Text
instanceId :: Text
$sel:queueConfigs:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> NonEmpty RoutingProfileQueueConfig
$sel:routingProfileId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> Text
$sel:instanceId:AssociateRoutingProfileQueues' :: AssociateRoutingProfileQueues -> 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
"/associate-queues"
      ]

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

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

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

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