{-# 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.UpdateQueueMaxContacts
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Updates the maximum number of contacts allowed in a queue before it is
-- considered full.
module Amazonka.Connect.UpdateQueueMaxContacts
  ( -- * Creating a Request
    UpdateQueueMaxContacts (..),
    newUpdateQueueMaxContacts,

    -- * Request Lenses
    updateQueueMaxContacts_maxContacts,
    updateQueueMaxContacts_instanceId,
    updateQueueMaxContacts_queueId,

    -- * Destructuring the Response
    UpdateQueueMaxContactsResponse (..),
    newUpdateQueueMaxContactsResponse,
  )
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:/ 'newUpdateQueueMaxContacts' smart constructor.
data UpdateQueueMaxContacts = UpdateQueueMaxContacts'
  { -- | The maximum number of contacts that can be in the queue before it is
    -- considered full.
    UpdateQueueMaxContacts -> Maybe Natural
maxContacts :: Prelude.Maybe Prelude.Natural,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    UpdateQueueMaxContacts -> Text
instanceId :: Prelude.Text,
    -- | The identifier for the queue.
    UpdateQueueMaxContacts -> Text
queueId :: Prelude.Text
  }
  deriving (UpdateQueueMaxContacts -> UpdateQueueMaxContacts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateQueueMaxContacts -> UpdateQueueMaxContacts -> Bool
$c/= :: UpdateQueueMaxContacts -> UpdateQueueMaxContacts -> Bool
== :: UpdateQueueMaxContacts -> UpdateQueueMaxContacts -> Bool
$c== :: UpdateQueueMaxContacts -> UpdateQueueMaxContacts -> Bool
Prelude.Eq, ReadPrec [UpdateQueueMaxContacts]
ReadPrec UpdateQueueMaxContacts
Int -> ReadS UpdateQueueMaxContacts
ReadS [UpdateQueueMaxContacts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateQueueMaxContacts]
$creadListPrec :: ReadPrec [UpdateQueueMaxContacts]
readPrec :: ReadPrec UpdateQueueMaxContacts
$creadPrec :: ReadPrec UpdateQueueMaxContacts
readList :: ReadS [UpdateQueueMaxContacts]
$creadList :: ReadS [UpdateQueueMaxContacts]
readsPrec :: Int -> ReadS UpdateQueueMaxContacts
$creadsPrec :: Int -> ReadS UpdateQueueMaxContacts
Prelude.Read, Int -> UpdateQueueMaxContacts -> ShowS
[UpdateQueueMaxContacts] -> ShowS
UpdateQueueMaxContacts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateQueueMaxContacts] -> ShowS
$cshowList :: [UpdateQueueMaxContacts] -> ShowS
show :: UpdateQueueMaxContacts -> String
$cshow :: UpdateQueueMaxContacts -> String
showsPrec :: Int -> UpdateQueueMaxContacts -> ShowS
$cshowsPrec :: Int -> UpdateQueueMaxContacts -> ShowS
Prelude.Show, forall x. Rep UpdateQueueMaxContacts x -> UpdateQueueMaxContacts
forall x. UpdateQueueMaxContacts -> Rep UpdateQueueMaxContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateQueueMaxContacts x -> UpdateQueueMaxContacts
$cfrom :: forall x. UpdateQueueMaxContacts -> Rep UpdateQueueMaxContacts x
Prelude.Generic)

-- |
-- Create a value of 'UpdateQueueMaxContacts' 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:
--
-- 'maxContacts', 'updateQueueMaxContacts_maxContacts' - The maximum number of contacts that can be in the queue before it is
-- considered full.
--
-- 'instanceId', 'updateQueueMaxContacts_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'queueId', 'updateQueueMaxContacts_queueId' - The identifier for the queue.
newUpdateQueueMaxContacts ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'queueId'
  Prelude.Text ->
  UpdateQueueMaxContacts
newUpdateQueueMaxContacts :: Text -> Text -> UpdateQueueMaxContacts
newUpdateQueueMaxContacts Text
pInstanceId_ Text
pQueueId_ =
  UpdateQueueMaxContacts'
    { $sel:maxContacts:UpdateQueueMaxContacts' :: Maybe Natural
maxContacts =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:UpdateQueueMaxContacts' :: Text
instanceId = Text
pInstanceId_,
      $sel:queueId:UpdateQueueMaxContacts' :: Text
queueId = Text
pQueueId_
    }

-- | The maximum number of contacts that can be in the queue before it is
-- considered full.
updateQueueMaxContacts_maxContacts :: Lens.Lens' UpdateQueueMaxContacts (Prelude.Maybe Prelude.Natural)
updateQueueMaxContacts_maxContacts :: Lens' UpdateQueueMaxContacts (Maybe Natural)
updateQueueMaxContacts_maxContacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateQueueMaxContacts' {Maybe Natural
maxContacts :: Maybe Natural
$sel:maxContacts:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Maybe Natural
maxContacts} -> Maybe Natural
maxContacts) (\s :: UpdateQueueMaxContacts
s@UpdateQueueMaxContacts' {} Maybe Natural
a -> UpdateQueueMaxContacts
s {$sel:maxContacts:UpdateQueueMaxContacts' :: Maybe Natural
maxContacts = Maybe Natural
a} :: UpdateQueueMaxContacts)

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

-- | The identifier for the queue.
updateQueueMaxContacts_queueId :: Lens.Lens' UpdateQueueMaxContacts Prelude.Text
updateQueueMaxContacts_queueId :: Lens' UpdateQueueMaxContacts Text
updateQueueMaxContacts_queueId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateQueueMaxContacts' {Text
queueId :: Text
$sel:queueId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
queueId} -> Text
queueId) (\s :: UpdateQueueMaxContacts
s@UpdateQueueMaxContacts' {} Text
a -> UpdateQueueMaxContacts
s {$sel:queueId:UpdateQueueMaxContacts' :: Text
queueId = Text
a} :: UpdateQueueMaxContacts)

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

instance Prelude.Hashable UpdateQueueMaxContacts where
  hashWithSalt :: Int -> UpdateQueueMaxContacts -> Int
hashWithSalt Int
_salt UpdateQueueMaxContacts' {Maybe Natural
Text
queueId :: Text
instanceId :: Text
maxContacts :: Maybe Natural
$sel:queueId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:instanceId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:maxContacts:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxContacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
queueId

instance Prelude.NFData UpdateQueueMaxContacts where
  rnf :: UpdateQueueMaxContacts -> ()
rnf UpdateQueueMaxContacts' {Maybe Natural
Text
queueId :: Text
instanceId :: Text
maxContacts :: Maybe Natural
$sel:queueId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:instanceId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:maxContacts:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxContacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
queueId

instance Data.ToHeaders UpdateQueueMaxContacts where
  toHeaders :: UpdateQueueMaxContacts -> [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 UpdateQueueMaxContacts where
  toJSON :: UpdateQueueMaxContacts -> Value
toJSON UpdateQueueMaxContacts' {Maybe Natural
Text
queueId :: Text
instanceId :: Text
maxContacts :: Maybe Natural
$sel:queueId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:instanceId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:maxContacts:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"MaxContacts" 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 Natural
maxContacts]
      )

instance Data.ToPath UpdateQueueMaxContacts where
  toPath :: UpdateQueueMaxContacts -> ByteString
toPath UpdateQueueMaxContacts' {Maybe Natural
Text
queueId :: Text
instanceId :: Text
maxContacts :: Maybe Natural
$sel:queueId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:instanceId:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Text
$sel:maxContacts:UpdateQueueMaxContacts' :: UpdateQueueMaxContacts -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/queues/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
queueId,
        ByteString
"/max-contacts"
      ]

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

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

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

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