{-# 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.UpdateConfiguration
-- 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 an MSK configuration.
module Amazonka.Kafka.UpdateConfiguration
  ( -- * Creating a Request
    UpdateConfiguration (..),
    newUpdateConfiguration,

    -- * Request Lenses
    updateConfiguration_description,
    updateConfiguration_arn,
    updateConfiguration_serverProperties,

    -- * Destructuring the Response
    UpdateConfigurationResponse (..),
    newUpdateConfigurationResponse,

    -- * Response Lenses
    updateConfigurationResponse_arn,
    updateConfigurationResponse_latestRevision,
    updateConfigurationResponse_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

-- | /See:/ 'newUpdateConfiguration' smart constructor.
data UpdateConfiguration = UpdateConfiguration'
  { -- | The description of the configuration revision.
    UpdateConfiguration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the configuration.
    UpdateConfiguration -> Text
arn :: Prelude.Text,
    -- | Contents of the server.properties file. When using the API, you must
    -- ensure that the contents of the file are base64 encoded. When using the
    -- AWS Management Console, the SDK, or the AWS CLI, the contents of
    -- server.properties can be in plaintext.
    UpdateConfiguration -> Base64
serverProperties :: Data.Base64
  }
  deriving (UpdateConfiguration -> UpdateConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConfiguration -> UpdateConfiguration -> Bool
$c/= :: UpdateConfiguration -> UpdateConfiguration -> Bool
== :: UpdateConfiguration -> UpdateConfiguration -> Bool
$c== :: UpdateConfiguration -> UpdateConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateConfiguration]
ReadPrec UpdateConfiguration
Int -> ReadS UpdateConfiguration
ReadS [UpdateConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConfiguration]
$creadListPrec :: ReadPrec [UpdateConfiguration]
readPrec :: ReadPrec UpdateConfiguration
$creadPrec :: ReadPrec UpdateConfiguration
readList :: ReadS [UpdateConfiguration]
$creadList :: ReadS [UpdateConfiguration]
readsPrec :: Int -> ReadS UpdateConfiguration
$creadsPrec :: Int -> ReadS UpdateConfiguration
Prelude.Read, Int -> UpdateConfiguration -> ShowS
[UpdateConfiguration] -> ShowS
UpdateConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConfiguration] -> ShowS
$cshowList :: [UpdateConfiguration] -> ShowS
show :: UpdateConfiguration -> String
$cshow :: UpdateConfiguration -> String
showsPrec :: Int -> UpdateConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateConfiguration -> ShowS
Prelude.Show, forall x. Rep UpdateConfiguration x -> UpdateConfiguration
forall x. UpdateConfiguration -> Rep UpdateConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateConfiguration x -> UpdateConfiguration
$cfrom :: forall x. UpdateConfiguration -> Rep UpdateConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConfiguration' 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:
--
-- 'description', 'updateConfiguration_description' - The description of the configuration revision.
--
-- 'arn', 'updateConfiguration_arn' - The Amazon Resource Name (ARN) of the configuration.
--
-- 'serverProperties', 'updateConfiguration_serverProperties' - Contents of the server.properties file. When using the API, you must
-- ensure that the contents of the file are base64 encoded. When using the
-- AWS Management Console, the SDK, or the AWS CLI, the contents of
-- server.properties can be in plaintext.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
newUpdateConfiguration ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'serverProperties'
  Prelude.ByteString ->
  UpdateConfiguration
newUpdateConfiguration :: Text -> ByteString -> UpdateConfiguration
newUpdateConfiguration Text
pArn_ ByteString
pServerProperties_ =
  UpdateConfiguration'
    { $sel:description:UpdateConfiguration' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:UpdateConfiguration' :: Text
arn = Text
pArn_,
      $sel:serverProperties:UpdateConfiguration' :: Base64
serverProperties =
        Iso' Base64 ByteString
Data._Base64 forall t b. AReview t b -> b -> t
Lens.# ByteString
pServerProperties_
    }

-- | The description of the configuration revision.
updateConfiguration_description :: Lens.Lens' UpdateConfiguration (Prelude.Maybe Prelude.Text)
updateConfiguration_description :: Lens' UpdateConfiguration (Maybe Text)
updateConfiguration_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfiguration' {Maybe Text
description :: Maybe Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateConfiguration
s@UpdateConfiguration' {} Maybe Text
a -> UpdateConfiguration
s {$sel:description:UpdateConfiguration' :: Maybe Text
description = Maybe Text
a} :: UpdateConfiguration)

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

-- | Contents of the server.properties file. When using the API, you must
-- ensure that the contents of the file are base64 encoded. When using the
-- AWS Management Console, the SDK, or the AWS CLI, the contents of
-- server.properties can be in plaintext.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
updateConfiguration_serverProperties :: Lens.Lens' UpdateConfiguration Prelude.ByteString
updateConfiguration_serverProperties :: Lens' UpdateConfiguration ByteString
updateConfiguration_serverProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfiguration' {Base64
serverProperties :: Base64
$sel:serverProperties:UpdateConfiguration' :: UpdateConfiguration -> Base64
serverProperties} -> Base64
serverProperties) (\s :: UpdateConfiguration
s@UpdateConfiguration' {} Base64
a -> UpdateConfiguration
s {$sel:serverProperties:UpdateConfiguration' :: Base64
serverProperties = Base64
a} :: UpdateConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

instance Core.AWSRequest UpdateConfiguration where
  type
    AWSResponse UpdateConfiguration =
      UpdateConfigurationResponse
  request :: (Service -> Service)
-> UpdateConfiguration -> Request UpdateConfiguration
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 UpdateConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateConfiguration)))
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 ConfigurationRevision
-> Int
-> UpdateConfigurationResponse
UpdateConfigurationResponse'
            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
"arn")
            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
"latestRevision")
            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 UpdateConfiguration where
  hashWithSalt :: Int -> UpdateConfiguration -> Int
hashWithSalt Int
_salt UpdateConfiguration' {Maybe Text
Text
Base64
serverProperties :: Base64
arn :: Text
description :: Maybe Text
$sel:serverProperties:UpdateConfiguration' :: UpdateConfiguration -> Base64
$sel:arn:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Base64
serverProperties

instance Prelude.NFData UpdateConfiguration where
  rnf :: UpdateConfiguration -> ()
rnf UpdateConfiguration' {Maybe Text
Text
Base64
serverProperties :: Base64
arn :: Text
description :: Maybe Text
$sel:serverProperties:UpdateConfiguration' :: UpdateConfiguration -> Base64
$sel:arn:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Base64
serverProperties

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

instance Data.ToPath UpdateConfiguration where
  toPath :: UpdateConfiguration -> ByteString
toPath UpdateConfiguration' {Maybe Text
Text
Base64
serverProperties :: Base64
arn :: Text
description :: Maybe Text
$sel:serverProperties:UpdateConfiguration' :: UpdateConfiguration -> Base64
$sel:arn:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/configurations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
arn]

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

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

-- |
-- Create a value of 'UpdateConfigurationResponse' 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:
--
-- 'arn', 'updateConfigurationResponse_arn' - The Amazon Resource Name (ARN) of the configuration.
--
-- 'latestRevision', 'updateConfigurationResponse_latestRevision' - Latest revision of the configuration.
--
-- 'httpStatus', 'updateConfigurationResponse_httpStatus' - The response's http status code.
newUpdateConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConfigurationResponse
newUpdateConfigurationResponse :: Int -> UpdateConfigurationResponse
newUpdateConfigurationResponse Int
pHttpStatus_ =
  UpdateConfigurationResponse'
    { $sel:arn:UpdateConfigurationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:latestRevision:UpdateConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Latest revision of the configuration.
updateConfigurationResponse_latestRevision :: Lens.Lens' UpdateConfigurationResponse (Prelude.Maybe ConfigurationRevision)
updateConfigurationResponse_latestRevision :: Lens' UpdateConfigurationResponse (Maybe ConfigurationRevision)
updateConfigurationResponse_latestRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationResponse' {Maybe ConfigurationRevision
latestRevision :: Maybe ConfigurationRevision
$sel:latestRevision:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe ConfigurationRevision
latestRevision} -> Maybe ConfigurationRevision
latestRevision) (\s :: UpdateConfigurationResponse
s@UpdateConfigurationResponse' {} Maybe ConfigurationRevision
a -> UpdateConfigurationResponse
s {$sel:latestRevision:UpdateConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = Maybe ConfigurationRevision
a} :: UpdateConfigurationResponse)

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

instance Prelude.NFData UpdateConfigurationResponse where
  rnf :: UpdateConfigurationResponse -> ()
rnf UpdateConfigurationResponse' {Int
Maybe Text
Maybe ConfigurationRevision
httpStatus :: Int
latestRevision :: Maybe ConfigurationRevision
arn :: Maybe Text
$sel:httpStatus:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Int
$sel:latestRevision:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe ConfigurationRevision
$sel:arn:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfigurationRevision
latestRevision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus