{-# 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.UpdateMonitoring
-- 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 monitoring settings for the cluster. You can use this
-- operation to specify which Apache Kafka metrics you want Amazon MSK to
-- send to Amazon CloudWatch. You can also specify settings for open
-- monitoring with Prometheus.
module Amazonka.Kafka.UpdateMonitoring
  ( -- * Creating a Request
    UpdateMonitoring (..),
    newUpdateMonitoring,

    -- * Request Lenses
    updateMonitoring_enhancedMonitoring,
    updateMonitoring_loggingInfo,
    updateMonitoring_openMonitoring,
    updateMonitoring_clusterArn,
    updateMonitoring_currentVersion,

    -- * Destructuring the Response
    UpdateMonitoringResponse (..),
    newUpdateMonitoringResponse,

    -- * Response Lenses
    updateMonitoringResponse_clusterArn,
    updateMonitoringResponse_clusterOperationArn,
    updateMonitoringResponse_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 UpdateMonitoring.
--
-- /See:/ 'newUpdateMonitoring' smart constructor.
data UpdateMonitoring = UpdateMonitoring'
  { -- | Specifies which Apache Kafka metrics Amazon MSK gathers and sends to
    -- Amazon CloudWatch for this cluster.
    UpdateMonitoring -> Maybe EnhancedMonitoring
enhancedMonitoring :: Prelude.Maybe EnhancedMonitoring,
    UpdateMonitoring -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The settings for open monitoring.
    UpdateMonitoring -> Maybe OpenMonitoringInfo
openMonitoring :: Prelude.Maybe OpenMonitoringInfo,
    -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    UpdateMonitoring -> Text
clusterArn :: Prelude.Text,
    -- | 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.
    UpdateMonitoring -> Text
currentVersion :: Prelude.Text
  }
  deriving (UpdateMonitoring -> UpdateMonitoring -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMonitoring -> UpdateMonitoring -> Bool
$c/= :: UpdateMonitoring -> UpdateMonitoring -> Bool
== :: UpdateMonitoring -> UpdateMonitoring -> Bool
$c== :: UpdateMonitoring -> UpdateMonitoring -> Bool
Prelude.Eq, ReadPrec [UpdateMonitoring]
ReadPrec UpdateMonitoring
Int -> ReadS UpdateMonitoring
ReadS [UpdateMonitoring]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateMonitoring]
$creadListPrec :: ReadPrec [UpdateMonitoring]
readPrec :: ReadPrec UpdateMonitoring
$creadPrec :: ReadPrec UpdateMonitoring
readList :: ReadS [UpdateMonitoring]
$creadList :: ReadS [UpdateMonitoring]
readsPrec :: Int -> ReadS UpdateMonitoring
$creadsPrec :: Int -> ReadS UpdateMonitoring
Prelude.Read, Int -> UpdateMonitoring -> ShowS
[UpdateMonitoring] -> ShowS
UpdateMonitoring -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMonitoring] -> ShowS
$cshowList :: [UpdateMonitoring] -> ShowS
show :: UpdateMonitoring -> String
$cshow :: UpdateMonitoring -> String
showsPrec :: Int -> UpdateMonitoring -> ShowS
$cshowsPrec :: Int -> UpdateMonitoring -> ShowS
Prelude.Show, forall x. Rep UpdateMonitoring x -> UpdateMonitoring
forall x. UpdateMonitoring -> Rep UpdateMonitoring x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateMonitoring x -> UpdateMonitoring
$cfrom :: forall x. UpdateMonitoring -> Rep UpdateMonitoring x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMonitoring' 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:
--
-- 'enhancedMonitoring', 'updateMonitoring_enhancedMonitoring' - Specifies which Apache Kafka metrics Amazon MSK gathers and sends to
-- Amazon CloudWatch for this cluster.
--
-- 'loggingInfo', 'updateMonitoring_loggingInfo' - Undocumented member.
--
-- 'openMonitoring', 'updateMonitoring_openMonitoring' - The settings for open monitoring.
--
-- 'clusterArn', 'updateMonitoring_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
--
-- 'currentVersion', 'updateMonitoring_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.
newUpdateMonitoring ::
  -- | 'clusterArn'
  Prelude.Text ->
  -- | 'currentVersion'
  Prelude.Text ->
  UpdateMonitoring
newUpdateMonitoring :: Text -> Text -> UpdateMonitoring
newUpdateMonitoring Text
pClusterArn_ Text
pCurrentVersion_ =
  UpdateMonitoring'
    { $sel:enhancedMonitoring:UpdateMonitoring' :: Maybe EnhancedMonitoring
enhancedMonitoring =
        forall a. Maybe a
Prelude.Nothing,
      $sel:loggingInfo:UpdateMonitoring' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:openMonitoring:UpdateMonitoring' :: Maybe OpenMonitoringInfo
openMonitoring = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterArn:UpdateMonitoring' :: Text
clusterArn = Text
pClusterArn_,
      $sel:currentVersion:UpdateMonitoring' :: Text
currentVersion = Text
pCurrentVersion_
    }

-- | Specifies which Apache Kafka metrics Amazon MSK gathers and sends to
-- Amazon CloudWatch for this cluster.
updateMonitoring_enhancedMonitoring :: Lens.Lens' UpdateMonitoring (Prelude.Maybe EnhancedMonitoring)
updateMonitoring_enhancedMonitoring :: Lens' UpdateMonitoring (Maybe EnhancedMonitoring)
updateMonitoring_enhancedMonitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMonitoring' {Maybe EnhancedMonitoring
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:enhancedMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe EnhancedMonitoring
enhancedMonitoring} -> Maybe EnhancedMonitoring
enhancedMonitoring) (\s :: UpdateMonitoring
s@UpdateMonitoring' {} Maybe EnhancedMonitoring
a -> UpdateMonitoring
s {$sel:enhancedMonitoring:UpdateMonitoring' :: Maybe EnhancedMonitoring
enhancedMonitoring = Maybe EnhancedMonitoring
a} :: UpdateMonitoring)

-- | Undocumented member.
updateMonitoring_loggingInfo :: Lens.Lens' UpdateMonitoring (Prelude.Maybe LoggingInfo)
updateMonitoring_loggingInfo :: Lens' UpdateMonitoring (Maybe LoggingInfo)
updateMonitoring_loggingInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMonitoring' {Maybe LoggingInfo
loggingInfo :: Maybe LoggingInfo
$sel:loggingInfo:UpdateMonitoring' :: UpdateMonitoring -> Maybe LoggingInfo
loggingInfo} -> Maybe LoggingInfo
loggingInfo) (\s :: UpdateMonitoring
s@UpdateMonitoring' {} Maybe LoggingInfo
a -> UpdateMonitoring
s {$sel:loggingInfo:UpdateMonitoring' :: Maybe LoggingInfo
loggingInfo = Maybe LoggingInfo
a} :: UpdateMonitoring)

-- | The settings for open monitoring.
updateMonitoring_openMonitoring :: Lens.Lens' UpdateMonitoring (Prelude.Maybe OpenMonitoringInfo)
updateMonitoring_openMonitoring :: Lens' UpdateMonitoring (Maybe OpenMonitoringInfo)
updateMonitoring_openMonitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMonitoring' {Maybe OpenMonitoringInfo
openMonitoring :: Maybe OpenMonitoringInfo
$sel:openMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe OpenMonitoringInfo
openMonitoring} -> Maybe OpenMonitoringInfo
openMonitoring) (\s :: UpdateMonitoring
s@UpdateMonitoring' {} Maybe OpenMonitoringInfo
a -> UpdateMonitoring
s {$sel:openMonitoring:UpdateMonitoring' :: Maybe OpenMonitoringInfo
openMonitoring = Maybe OpenMonitoringInfo
a} :: UpdateMonitoring)

-- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
updateMonitoring_clusterArn :: Lens.Lens' UpdateMonitoring Prelude.Text
updateMonitoring_clusterArn :: Lens' UpdateMonitoring Text
updateMonitoring_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMonitoring' {Text
clusterArn :: Text
$sel:clusterArn:UpdateMonitoring' :: UpdateMonitoring -> Text
clusterArn} -> Text
clusterArn) (\s :: UpdateMonitoring
s@UpdateMonitoring' {} Text
a -> UpdateMonitoring
s {$sel:clusterArn:UpdateMonitoring' :: Text
clusterArn = Text
a} :: UpdateMonitoring)

-- | 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.
updateMonitoring_currentVersion :: Lens.Lens' UpdateMonitoring Prelude.Text
updateMonitoring_currentVersion :: Lens' UpdateMonitoring Text
updateMonitoring_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMonitoring' {Text
currentVersion :: Text
$sel:currentVersion:UpdateMonitoring' :: UpdateMonitoring -> Text
currentVersion} -> Text
currentVersion) (\s :: UpdateMonitoring
s@UpdateMonitoring' {} Text
a -> UpdateMonitoring
s {$sel:currentVersion:UpdateMonitoring' :: Text
currentVersion = Text
a} :: UpdateMonitoring)

instance Core.AWSRequest UpdateMonitoring where
  type
    AWSResponse UpdateMonitoring =
      UpdateMonitoringResponse
  request :: (Service -> Service)
-> UpdateMonitoring -> Request UpdateMonitoring
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 UpdateMonitoring
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateMonitoring)))
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 -> UpdateMonitoringResponse
UpdateMonitoringResponse'
            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 UpdateMonitoring where
  hashWithSalt :: Int -> UpdateMonitoring -> Int
hashWithSalt Int
_salt UpdateMonitoring' {Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Text
currentVersion :: Text
clusterArn :: Text
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:currentVersion:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:clusterArn:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:openMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe OpenMonitoringInfo
$sel:loggingInfo:UpdateMonitoring' :: UpdateMonitoring -> Maybe LoggingInfo
$sel:enhancedMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe EnhancedMonitoring
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnhancedMonitoring
enhancedMonitoring
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoggingInfo
loggingInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenMonitoringInfo
openMonitoring
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
currentVersion

instance Prelude.NFData UpdateMonitoring where
  rnf :: UpdateMonitoring -> ()
rnf UpdateMonitoring' {Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Text
currentVersion :: Text
clusterArn :: Text
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:currentVersion:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:clusterArn:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:openMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe OpenMonitoringInfo
$sel:loggingInfo:UpdateMonitoring' :: UpdateMonitoring -> Maybe LoggingInfo
$sel:enhancedMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe EnhancedMonitoring
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EnhancedMonitoring
enhancedMonitoring
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoggingInfo
loggingInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpenMonitoringInfo
openMonitoring
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
currentVersion

instance Data.ToHeaders UpdateMonitoring where
  toHeaders :: UpdateMonitoring -> 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 UpdateMonitoring where
  toJSON :: UpdateMonitoring -> Value
toJSON UpdateMonitoring' {Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Text
currentVersion :: Text
clusterArn :: Text
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:currentVersion:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:clusterArn:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:openMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe OpenMonitoringInfo
$sel:loggingInfo:UpdateMonitoring' :: UpdateMonitoring -> Maybe LoggingInfo
$sel:enhancedMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe EnhancedMonitoring
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"enhancedMonitoring" 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 EnhancedMonitoring
enhancedMonitoring,
            (Key
"loggingInfo" 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 LoggingInfo
loggingInfo,
            (Key
"openMonitoring" 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 OpenMonitoringInfo
openMonitoring,
            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 UpdateMonitoring where
  toPath :: UpdateMonitoring -> ByteString
toPath UpdateMonitoring' {Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Text
currentVersion :: Text
clusterArn :: Text
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:currentVersion:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:clusterArn:UpdateMonitoring' :: UpdateMonitoring -> Text
$sel:openMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe OpenMonitoringInfo
$sel:loggingInfo:UpdateMonitoring' :: UpdateMonitoring -> Maybe LoggingInfo
$sel:enhancedMonitoring:UpdateMonitoring' :: UpdateMonitoring -> Maybe EnhancedMonitoring
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/clusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn,
        ByteString
"/monitoring"
      ]

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

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

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

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

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

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

instance Prelude.NFData UpdateMonitoringResponse where
  rnf :: UpdateMonitoringResponse -> ()
rnf UpdateMonitoringResponse' {Int
Maybe Text
httpStatus :: Int
clusterOperationArn :: Maybe Text
clusterArn :: Maybe Text
$sel:httpStatus:UpdateMonitoringResponse' :: UpdateMonitoringResponse -> Int
$sel:clusterOperationArn:UpdateMonitoringResponse' :: UpdateMonitoringResponse -> Maybe Text
$sel:clusterArn:UpdateMonitoringResponse' :: UpdateMonitoringResponse -> 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