{-# 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.UpdateQuickConnectConfig
-- 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 configuration settings for the specified quick connect.
module Amazonka.Connect.UpdateQuickConnectConfig
  ( -- * Creating a Request
    UpdateQuickConnectConfig (..),
    newUpdateQuickConnectConfig,

    -- * Request Lenses
    updateQuickConnectConfig_instanceId,
    updateQuickConnectConfig_quickConnectId,
    updateQuickConnectConfig_quickConnectConfig,

    -- * Destructuring the Response
    UpdateQuickConnectConfigResponse (..),
    newUpdateQuickConnectConfigResponse,
  )
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:/ 'newUpdateQuickConnectConfig' smart constructor.
data UpdateQuickConnectConfig = UpdateQuickConnectConfig'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    UpdateQuickConnectConfig -> Text
instanceId :: Prelude.Text,
    -- | The identifier for the quick connect.
    UpdateQuickConnectConfig -> Text
quickConnectId :: Prelude.Text,
    -- | Information about the configuration settings for the quick connect.
    UpdateQuickConnectConfig -> QuickConnectConfig
quickConnectConfig :: QuickConnectConfig
  }
  deriving (UpdateQuickConnectConfig -> UpdateQuickConnectConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateQuickConnectConfig -> UpdateQuickConnectConfig -> Bool
$c/= :: UpdateQuickConnectConfig -> UpdateQuickConnectConfig -> Bool
== :: UpdateQuickConnectConfig -> UpdateQuickConnectConfig -> Bool
$c== :: UpdateQuickConnectConfig -> UpdateQuickConnectConfig -> Bool
Prelude.Eq, ReadPrec [UpdateQuickConnectConfig]
ReadPrec UpdateQuickConnectConfig
Int -> ReadS UpdateQuickConnectConfig
ReadS [UpdateQuickConnectConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateQuickConnectConfig]
$creadListPrec :: ReadPrec [UpdateQuickConnectConfig]
readPrec :: ReadPrec UpdateQuickConnectConfig
$creadPrec :: ReadPrec UpdateQuickConnectConfig
readList :: ReadS [UpdateQuickConnectConfig]
$creadList :: ReadS [UpdateQuickConnectConfig]
readsPrec :: Int -> ReadS UpdateQuickConnectConfig
$creadsPrec :: Int -> ReadS UpdateQuickConnectConfig
Prelude.Read, Int -> UpdateQuickConnectConfig -> ShowS
[UpdateQuickConnectConfig] -> ShowS
UpdateQuickConnectConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateQuickConnectConfig] -> ShowS
$cshowList :: [UpdateQuickConnectConfig] -> ShowS
show :: UpdateQuickConnectConfig -> String
$cshow :: UpdateQuickConnectConfig -> String
showsPrec :: Int -> UpdateQuickConnectConfig -> ShowS
$cshowsPrec :: Int -> UpdateQuickConnectConfig -> ShowS
Prelude.Show, forall x.
Rep UpdateQuickConnectConfig x -> UpdateQuickConnectConfig
forall x.
UpdateQuickConnectConfig -> Rep UpdateQuickConnectConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateQuickConnectConfig x -> UpdateQuickConnectConfig
$cfrom :: forall x.
UpdateQuickConnectConfig -> Rep UpdateQuickConnectConfig x
Prelude.Generic)

-- |
-- Create a value of 'UpdateQuickConnectConfig' 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', 'updateQuickConnectConfig_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'quickConnectId', 'updateQuickConnectConfig_quickConnectId' - The identifier for the quick connect.
--
-- 'quickConnectConfig', 'updateQuickConnectConfig_quickConnectConfig' - Information about the configuration settings for the quick connect.
newUpdateQuickConnectConfig ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'quickConnectId'
  Prelude.Text ->
  -- | 'quickConnectConfig'
  QuickConnectConfig ->
  UpdateQuickConnectConfig
newUpdateQuickConnectConfig :: Text -> Text -> QuickConnectConfig -> UpdateQuickConnectConfig
newUpdateQuickConnectConfig
  Text
pInstanceId_
  Text
pQuickConnectId_
  QuickConnectConfig
pQuickConnectConfig_ =
    UpdateQuickConnectConfig'
      { $sel:instanceId:UpdateQuickConnectConfig' :: Text
instanceId =
          Text
pInstanceId_,
        $sel:quickConnectId:UpdateQuickConnectConfig' :: Text
quickConnectId = Text
pQuickConnectId_,
        $sel:quickConnectConfig:UpdateQuickConnectConfig' :: QuickConnectConfig
quickConnectConfig = QuickConnectConfig
pQuickConnectConfig_
      }

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

-- | The identifier for the quick connect.
updateQuickConnectConfig_quickConnectId :: Lens.Lens' UpdateQuickConnectConfig Prelude.Text
updateQuickConnectConfig_quickConnectId :: Lens' UpdateQuickConnectConfig Text
updateQuickConnectConfig_quickConnectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateQuickConnectConfig' {Text
quickConnectId :: Text
$sel:quickConnectId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
quickConnectId} -> Text
quickConnectId) (\s :: UpdateQuickConnectConfig
s@UpdateQuickConnectConfig' {} Text
a -> UpdateQuickConnectConfig
s {$sel:quickConnectId:UpdateQuickConnectConfig' :: Text
quickConnectId = Text
a} :: UpdateQuickConnectConfig)

-- | Information about the configuration settings for the quick connect.
updateQuickConnectConfig_quickConnectConfig :: Lens.Lens' UpdateQuickConnectConfig QuickConnectConfig
updateQuickConnectConfig_quickConnectConfig :: Lens' UpdateQuickConnectConfig QuickConnectConfig
updateQuickConnectConfig_quickConnectConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateQuickConnectConfig' {QuickConnectConfig
quickConnectConfig :: QuickConnectConfig
$sel:quickConnectConfig:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> QuickConnectConfig
quickConnectConfig} -> QuickConnectConfig
quickConnectConfig) (\s :: UpdateQuickConnectConfig
s@UpdateQuickConnectConfig' {} QuickConnectConfig
a -> UpdateQuickConnectConfig
s {$sel:quickConnectConfig:UpdateQuickConnectConfig' :: QuickConnectConfig
quickConnectConfig = QuickConnectConfig
a} :: UpdateQuickConnectConfig)

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

instance Prelude.Hashable UpdateQuickConnectConfig where
  hashWithSalt :: Int -> UpdateQuickConnectConfig -> Int
hashWithSalt Int
_salt UpdateQuickConnectConfig' {Text
QuickConnectConfig
quickConnectConfig :: QuickConnectConfig
quickConnectId :: Text
instanceId :: Text
$sel:quickConnectConfig:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> QuickConnectConfig
$sel:quickConnectId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
$sel:instanceId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
quickConnectId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` QuickConnectConfig
quickConnectConfig

instance Prelude.NFData UpdateQuickConnectConfig where
  rnf :: UpdateQuickConnectConfig -> ()
rnf UpdateQuickConnectConfig' {Text
QuickConnectConfig
quickConnectConfig :: QuickConnectConfig
quickConnectId :: Text
instanceId :: Text
$sel:quickConnectConfig:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> QuickConnectConfig
$sel:quickConnectId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
$sel:instanceId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> 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
quickConnectId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf QuickConnectConfig
quickConnectConfig

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

instance Data.ToPath UpdateQuickConnectConfig where
  toPath :: UpdateQuickConnectConfig -> ByteString
toPath UpdateQuickConnectConfig' {Text
QuickConnectConfig
quickConnectConfig :: QuickConnectConfig
quickConnectId :: Text
instanceId :: Text
$sel:quickConnectConfig:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> QuickConnectConfig
$sel:quickConnectId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
$sel:instanceId:UpdateQuickConnectConfig' :: UpdateQuickConnectConfig -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/quick-connects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
quickConnectId,
        ByteString
"/config"
      ]

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

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

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

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