{-# 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.Kafka.UpdateConnectivity
-- 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 cluster\'s connectivity configuration.
module Amazonka.Kafka.UpdateConnectivity
  ( -- * Creating a Request
    UpdateConnectivity (..),
    newUpdateConnectivity,

    -- * Request Lenses
    updateConnectivity_clusterArn,
    updateConnectivity_connectivityInfo,
    updateConnectivity_currentVersion,

    -- * Destructuring the Response
    UpdateConnectivityResponse (..),
    newUpdateConnectivityResponse,

    -- * Response Lenses
    updateConnectivityResponse_clusterArn,
    updateConnectivityResponse_clusterOperationArn,
    updateConnectivityResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kafka.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request body for UpdateConnectivity.
--
-- /See:/ 'newUpdateConnectivity' smart constructor.
data UpdateConnectivity = UpdateConnectivity'
  { -- | The Amazon Resource Name (ARN) of the configuration.
    UpdateConnectivity -> Text
clusterArn :: Prelude.Text,
    -- | Information about the broker access configuration.
    UpdateConnectivity -> ConnectivityInfo
connectivityInfo :: ConnectivityInfo,
    -- | The version of the MSK cluster to update. Cluster versions aren\'t
    -- simple numbers. You can describe an MSK cluster to find its version.
    -- When this update operation is successful, it generates a new cluster
    -- version.
    UpdateConnectivity -> Text
currentVersion :: Prelude.Text
  }
  deriving (UpdateConnectivity -> UpdateConnectivity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnectivity -> UpdateConnectivity -> Bool
$c/= :: UpdateConnectivity -> UpdateConnectivity -> Bool
== :: UpdateConnectivity -> UpdateConnectivity -> Bool
$c== :: UpdateConnectivity -> UpdateConnectivity -> Bool
Prelude.Eq, ReadPrec [UpdateConnectivity]
ReadPrec UpdateConnectivity
Int -> ReadS UpdateConnectivity
ReadS [UpdateConnectivity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnectivity]
$creadListPrec :: ReadPrec [UpdateConnectivity]
readPrec :: ReadPrec UpdateConnectivity
$creadPrec :: ReadPrec UpdateConnectivity
readList :: ReadS [UpdateConnectivity]
$creadList :: ReadS [UpdateConnectivity]
readsPrec :: Int -> ReadS UpdateConnectivity
$creadsPrec :: Int -> ReadS UpdateConnectivity
Prelude.Read, Int -> UpdateConnectivity -> ShowS
[UpdateConnectivity] -> ShowS
UpdateConnectivity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnectivity] -> ShowS
$cshowList :: [UpdateConnectivity] -> ShowS
show :: UpdateConnectivity -> String
$cshow :: UpdateConnectivity -> String
showsPrec :: Int -> UpdateConnectivity -> ShowS
$cshowsPrec :: Int -> UpdateConnectivity -> ShowS
Prelude.Show, forall x. Rep UpdateConnectivity x -> UpdateConnectivity
forall x. UpdateConnectivity -> Rep UpdateConnectivity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateConnectivity x -> UpdateConnectivity
$cfrom :: forall x. UpdateConnectivity -> Rep UpdateConnectivity x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnectivity' 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:
--
-- 'clusterArn', 'updateConnectivity_clusterArn' - The Amazon Resource Name (ARN) of the configuration.
--
-- 'connectivityInfo', 'updateConnectivity_connectivityInfo' - Information about the broker access configuration.
--
-- 'currentVersion', 'updateConnectivity_currentVersion' - The version of the MSK cluster to update. Cluster versions aren\'t
-- simple numbers. You can describe an MSK cluster to find its version.
-- When this update operation is successful, it generates a new cluster
-- version.
newUpdateConnectivity ::
  -- | 'clusterArn'
  Prelude.Text ->
  -- | 'connectivityInfo'
  ConnectivityInfo ->
  -- | 'currentVersion'
  Prelude.Text ->
  UpdateConnectivity
newUpdateConnectivity :: Text -> ConnectivityInfo -> Text -> UpdateConnectivity
newUpdateConnectivity
  Text
pClusterArn_
  ConnectivityInfo
pConnectivityInfo_
  Text
pCurrentVersion_ =
    UpdateConnectivity'
      { $sel:clusterArn:UpdateConnectivity' :: Text
clusterArn = Text
pClusterArn_,
        $sel:connectivityInfo:UpdateConnectivity' :: ConnectivityInfo
connectivityInfo = ConnectivityInfo
pConnectivityInfo_,
        $sel:currentVersion:UpdateConnectivity' :: Text
currentVersion = Text
pCurrentVersion_
      }

-- | The Amazon Resource Name (ARN) of the configuration.
updateConnectivity_clusterArn :: Lens.Lens' UpdateConnectivity Prelude.Text
updateConnectivity_clusterArn :: Lens' UpdateConnectivity Text
updateConnectivity_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivity' {Text
clusterArn :: Text
$sel:clusterArn:UpdateConnectivity' :: UpdateConnectivity -> Text
clusterArn} -> Text
clusterArn) (\s :: UpdateConnectivity
s@UpdateConnectivity' {} Text
a -> UpdateConnectivity
s {$sel:clusterArn:UpdateConnectivity' :: Text
clusterArn = Text
a} :: UpdateConnectivity)

-- | Information about the broker access configuration.
updateConnectivity_connectivityInfo :: Lens.Lens' UpdateConnectivity ConnectivityInfo
updateConnectivity_connectivityInfo :: Lens' UpdateConnectivity ConnectivityInfo
updateConnectivity_connectivityInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivity' {ConnectivityInfo
connectivityInfo :: ConnectivityInfo
$sel:connectivityInfo:UpdateConnectivity' :: UpdateConnectivity -> ConnectivityInfo
connectivityInfo} -> ConnectivityInfo
connectivityInfo) (\s :: UpdateConnectivity
s@UpdateConnectivity' {} ConnectivityInfo
a -> UpdateConnectivity
s {$sel:connectivityInfo:UpdateConnectivity' :: ConnectivityInfo
connectivityInfo = ConnectivityInfo
a} :: UpdateConnectivity)

-- | The version of the MSK cluster to update. Cluster versions aren\'t
-- simple numbers. You can describe an MSK cluster to find its version.
-- When this update operation is successful, it generates a new cluster
-- version.
updateConnectivity_currentVersion :: Lens.Lens' UpdateConnectivity Prelude.Text
updateConnectivity_currentVersion :: Lens' UpdateConnectivity Text
updateConnectivity_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivity' {Text
currentVersion :: Text
$sel:currentVersion:UpdateConnectivity' :: UpdateConnectivity -> Text
currentVersion} -> Text
currentVersion) (\s :: UpdateConnectivity
s@UpdateConnectivity' {} Text
a -> UpdateConnectivity
s {$sel:currentVersion:UpdateConnectivity' :: Text
currentVersion = Text
a} :: UpdateConnectivity)

instance Core.AWSRequest UpdateConnectivity where
  type
    AWSResponse UpdateConnectivity =
      UpdateConnectivityResponse
  request :: (Service -> Service)
-> UpdateConnectivity -> Request UpdateConnectivity
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateConnectivity
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateConnectivity)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> UpdateConnectivityResponse
UpdateConnectivityResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"clusterArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"clusterOperationArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateConnectivity where
  hashWithSalt :: Int -> UpdateConnectivity -> Int
hashWithSalt Int
_salt UpdateConnectivity' {Text
ConnectivityInfo
currentVersion :: Text
connectivityInfo :: ConnectivityInfo
clusterArn :: Text
$sel:currentVersion:UpdateConnectivity' :: UpdateConnectivity -> Text
$sel:connectivityInfo:UpdateConnectivity' :: UpdateConnectivity -> ConnectivityInfo
$sel:clusterArn:UpdateConnectivity' :: UpdateConnectivity -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ConnectivityInfo
connectivityInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
currentVersion

instance Prelude.NFData UpdateConnectivity where
  rnf :: UpdateConnectivity -> ()
rnf UpdateConnectivity' {Text
ConnectivityInfo
currentVersion :: Text
connectivityInfo :: ConnectivityInfo
clusterArn :: Text
$sel:currentVersion:UpdateConnectivity' :: UpdateConnectivity -> Text
$sel:connectivityInfo:UpdateConnectivity' :: UpdateConnectivity -> ConnectivityInfo
$sel:clusterArn:UpdateConnectivity' :: UpdateConnectivity -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ConnectivityInfo
connectivityInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
currentVersion

instance Data.ToHeaders UpdateConnectivity where
  toHeaders :: UpdateConnectivity -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateConnectivity where
  toJSON :: UpdateConnectivity -> Value
toJSON UpdateConnectivity' {Text
ConnectivityInfo
currentVersion :: Text
connectivityInfo :: ConnectivityInfo
clusterArn :: Text
$sel:currentVersion:UpdateConnectivity' :: UpdateConnectivity -> Text
$sel:connectivityInfo:UpdateConnectivity' :: UpdateConnectivity -> ConnectivityInfo
$sel:clusterArn:UpdateConnectivity' :: UpdateConnectivity -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"connectivityInfo" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ConnectivityInfo
connectivityInfo),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"currentVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
currentVersion)
          ]
      )

instance Data.ToPath UpdateConnectivity where
  toPath :: UpdateConnectivity -> ByteString
toPath UpdateConnectivity' {Text
ConnectivityInfo
currentVersion :: Text
connectivityInfo :: ConnectivityInfo
clusterArn :: Text
$sel:currentVersion:UpdateConnectivity' :: UpdateConnectivity -> Text
$sel:connectivityInfo:UpdateConnectivity' :: UpdateConnectivity -> ConnectivityInfo
$sel:clusterArn:UpdateConnectivity' :: UpdateConnectivity -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/clusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn,
        ByteString
"/connectivity"
      ]

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

-- | /See:/ 'newUpdateConnectivityResponse' smart constructor.
data UpdateConnectivityResponse = UpdateConnectivityResponse'
  { -- | The Amazon Resource Name (ARN) of the cluster.
    UpdateConnectivityResponse -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the cluster operation.
    UpdateConnectivityResponse -> Maybe Text
clusterOperationArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateConnectivityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateConnectivityResponse -> UpdateConnectivityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnectivityResponse -> UpdateConnectivityResponse -> Bool
$c/= :: UpdateConnectivityResponse -> UpdateConnectivityResponse -> Bool
== :: UpdateConnectivityResponse -> UpdateConnectivityResponse -> Bool
$c== :: UpdateConnectivityResponse -> UpdateConnectivityResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConnectivityResponse]
ReadPrec UpdateConnectivityResponse
Int -> ReadS UpdateConnectivityResponse
ReadS [UpdateConnectivityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnectivityResponse]
$creadListPrec :: ReadPrec [UpdateConnectivityResponse]
readPrec :: ReadPrec UpdateConnectivityResponse
$creadPrec :: ReadPrec UpdateConnectivityResponse
readList :: ReadS [UpdateConnectivityResponse]
$creadList :: ReadS [UpdateConnectivityResponse]
readsPrec :: Int -> ReadS UpdateConnectivityResponse
$creadsPrec :: Int -> ReadS UpdateConnectivityResponse
Prelude.Read, Int -> UpdateConnectivityResponse -> ShowS
[UpdateConnectivityResponse] -> ShowS
UpdateConnectivityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnectivityResponse] -> ShowS
$cshowList :: [UpdateConnectivityResponse] -> ShowS
show :: UpdateConnectivityResponse -> String
$cshow :: UpdateConnectivityResponse -> String
showsPrec :: Int -> UpdateConnectivityResponse -> ShowS
$cshowsPrec :: Int -> UpdateConnectivityResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConnectivityResponse x -> UpdateConnectivityResponse
forall x.
UpdateConnectivityResponse -> Rep UpdateConnectivityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConnectivityResponse x -> UpdateConnectivityResponse
$cfrom :: forall x.
UpdateConnectivityResponse -> Rep UpdateConnectivityResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnectivityResponse' 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:
--
-- 'clusterArn', 'updateConnectivityResponse_clusterArn' - The Amazon Resource Name (ARN) of the cluster.
--
-- 'clusterOperationArn', 'updateConnectivityResponse_clusterOperationArn' - The Amazon Resource Name (ARN) of the cluster operation.
--
-- 'httpStatus', 'updateConnectivityResponse_httpStatus' - The response's http status code.
newUpdateConnectivityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConnectivityResponse
newUpdateConnectivityResponse :: Int -> UpdateConnectivityResponse
newUpdateConnectivityResponse Int
pHttpStatus_ =
  UpdateConnectivityResponse'
    { $sel:clusterArn:UpdateConnectivityResponse' :: Maybe Text
clusterArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterOperationArn:UpdateConnectivityResponse' :: Maybe Text
clusterOperationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConnectivityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the cluster.
updateConnectivityResponse_clusterArn :: Lens.Lens' UpdateConnectivityResponse (Prelude.Maybe Prelude.Text)
updateConnectivityResponse_clusterArn :: Lens' UpdateConnectivityResponse (Maybe Text)
updateConnectivityResponse_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityResponse' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: UpdateConnectivityResponse
s@UpdateConnectivityResponse' {} Maybe Text
a -> UpdateConnectivityResponse
s {$sel:clusterArn:UpdateConnectivityResponse' :: Maybe Text
clusterArn = Maybe Text
a} :: UpdateConnectivityResponse)

-- | The Amazon Resource Name (ARN) of the cluster operation.
updateConnectivityResponse_clusterOperationArn :: Lens.Lens' UpdateConnectivityResponse (Prelude.Maybe Prelude.Text)
updateConnectivityResponse_clusterOperationArn :: Lens' UpdateConnectivityResponse (Maybe Text)
updateConnectivityResponse_clusterOperationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityResponse' {Maybe Text
clusterOperationArn :: Maybe Text
$sel:clusterOperationArn:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Maybe Text
clusterOperationArn} -> Maybe Text
clusterOperationArn) (\s :: UpdateConnectivityResponse
s@UpdateConnectivityResponse' {} Maybe Text
a -> UpdateConnectivityResponse
s {$sel:clusterOperationArn:UpdateConnectivityResponse' :: Maybe Text
clusterOperationArn = Maybe Text
a} :: UpdateConnectivityResponse)

-- | The response's http status code.
updateConnectivityResponse_httpStatus :: Lens.Lens' UpdateConnectivityResponse Prelude.Int
updateConnectivityResponse_httpStatus :: Lens' UpdateConnectivityResponse Int
updateConnectivityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateConnectivityResponse
s@UpdateConnectivityResponse' {} Int
a -> UpdateConnectivityResponse
s {$sel:httpStatus:UpdateConnectivityResponse' :: Int
httpStatus = Int
a} :: UpdateConnectivityResponse)

instance Prelude.NFData UpdateConnectivityResponse where
  rnf :: UpdateConnectivityResponse -> ()
rnf UpdateConnectivityResponse' {Int
Maybe Text
httpStatus :: Int
clusterOperationArn :: Maybe Text
clusterArn :: Maybe Text
$sel:httpStatus:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Int
$sel:clusterOperationArn:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Maybe Text
$sel:clusterArn:UpdateConnectivityResponse' :: UpdateConnectivityResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterOperationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus