{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ClusterInfo
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Kafka.Types.ClusterInfo 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.BrokerNodeGroupInfo
import Amazonka.Kafka.Types.BrokerSoftwareInfo
import Amazonka.Kafka.Types.ClientAuthentication
import Amazonka.Kafka.Types.ClusterState
import Amazonka.Kafka.Types.EncryptionInfo
import Amazonka.Kafka.Types.EnhancedMonitoring
import Amazonka.Kafka.Types.LoggingInfo
import Amazonka.Kafka.Types.OpenMonitoring
import Amazonka.Kafka.Types.StateInfo
import Amazonka.Kafka.Types.StorageMode
import qualified Amazonka.Prelude as Prelude

-- | Returns information about a cluster.
--
-- /See:/ 'newClusterInfo' smart constructor.
data ClusterInfo = ClusterInfo'
  { -- | Arn of active cluster operation.
    ClusterInfo -> Maybe Text
activeOperationArn :: Prelude.Maybe Prelude.Text,
    -- | Information about the broker nodes.
    ClusterInfo -> Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo :: Prelude.Maybe BrokerNodeGroupInfo,
    -- | Includes all client authentication information.
    ClusterInfo -> Maybe ClientAuthentication
clientAuthentication :: Prelude.Maybe ClientAuthentication,
    -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    ClusterInfo -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the cluster.
    ClusterInfo -> Maybe Text
clusterName :: Prelude.Maybe Prelude.Text,
    -- | The time when the cluster was created.
    ClusterInfo -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | Information about the version of software currently deployed on the
    -- Apache Kafka brokers in the cluster.
    ClusterInfo -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo :: Prelude.Maybe BrokerSoftwareInfo,
    -- | The current version of the MSK cluster.
    ClusterInfo -> Maybe Text
currentVersion :: Prelude.Maybe Prelude.Text,
    -- | Includes all encryption-related information.
    ClusterInfo -> Maybe EncryptionInfo
encryptionInfo :: Prelude.Maybe EncryptionInfo,
    -- | Specifies which metrics are gathered for the MSK cluster. This property
    -- has the following possible values: DEFAULT, PER_BROKER,
    -- PER_TOPIC_PER_BROKER, and PER_TOPIC_PER_PARTITION. For a list of the
    -- metrics associated with each of these levels of monitoring, see
    -- <https://docs.aws.amazon.com/msk/latest/developerguide/monitoring.html Monitoring>.
    ClusterInfo -> Maybe EnhancedMonitoring
enhancedMonitoring :: Prelude.Maybe EnhancedMonitoring,
    ClusterInfo -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The number of broker nodes in the cluster.
    ClusterInfo -> Maybe Int
numberOfBrokerNodes :: Prelude.Maybe Prelude.Int,
    -- | Settings for open monitoring using Prometheus.
    ClusterInfo -> Maybe OpenMonitoring
openMonitoring :: Prelude.Maybe OpenMonitoring,
    -- | The state of the cluster. The possible states are ACTIVE, CREATING,
    -- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
    ClusterInfo -> Maybe ClusterState
state :: Prelude.Maybe ClusterState,
    ClusterInfo -> Maybe StateInfo
stateInfo :: Prelude.Maybe StateInfo,
    -- | This controls storage mode for supported storage tiers.
    ClusterInfo -> Maybe StorageMode
storageMode :: Prelude.Maybe StorageMode,
    -- | Tags attached to the cluster.
    ClusterInfo -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The connection string to use to connect to the Apache ZooKeeper cluster.
    ClusterInfo -> Maybe Text
zookeeperConnectString :: Prelude.Maybe Prelude.Text,
    -- | The connection string to use to connect to zookeeper cluster on Tls
    -- port.
    ClusterInfo -> Maybe Text
zookeeperConnectStringTls :: Prelude.Maybe Prelude.Text
  }
  deriving (ClusterInfo -> ClusterInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClusterInfo -> ClusterInfo -> Bool
$c/= :: ClusterInfo -> ClusterInfo -> Bool
== :: ClusterInfo -> ClusterInfo -> Bool
$c== :: ClusterInfo -> ClusterInfo -> Bool
Prelude.Eq, ReadPrec [ClusterInfo]
ReadPrec ClusterInfo
Int -> ReadS ClusterInfo
ReadS [ClusterInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClusterInfo]
$creadListPrec :: ReadPrec [ClusterInfo]
readPrec :: ReadPrec ClusterInfo
$creadPrec :: ReadPrec ClusterInfo
readList :: ReadS [ClusterInfo]
$creadList :: ReadS [ClusterInfo]
readsPrec :: Int -> ReadS ClusterInfo
$creadsPrec :: Int -> ReadS ClusterInfo
Prelude.Read, Int -> ClusterInfo -> ShowS
[ClusterInfo] -> ShowS
ClusterInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClusterInfo] -> ShowS
$cshowList :: [ClusterInfo] -> ShowS
show :: ClusterInfo -> String
$cshow :: ClusterInfo -> String
showsPrec :: Int -> ClusterInfo -> ShowS
$cshowsPrec :: Int -> ClusterInfo -> ShowS
Prelude.Show, forall x. Rep ClusterInfo x -> ClusterInfo
forall x. ClusterInfo -> Rep ClusterInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClusterInfo x -> ClusterInfo
$cfrom :: forall x. ClusterInfo -> Rep ClusterInfo x
Prelude.Generic)

-- |
-- Create a value of 'ClusterInfo' 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:
--
-- 'activeOperationArn', 'clusterInfo_activeOperationArn' - Arn of active cluster operation.
--
-- 'brokerNodeGroupInfo', 'clusterInfo_brokerNodeGroupInfo' - Information about the broker nodes.
--
-- 'clientAuthentication', 'clusterInfo_clientAuthentication' - Includes all client authentication information.
--
-- 'clusterArn', 'clusterInfo_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
--
-- 'clusterName', 'clusterInfo_clusterName' - The name of the cluster.
--
-- 'creationTime', 'clusterInfo_creationTime' - The time when the cluster was created.
--
-- 'currentBrokerSoftwareInfo', 'clusterInfo_currentBrokerSoftwareInfo' - Information about the version of software currently deployed on the
-- Apache Kafka brokers in the cluster.
--
-- 'currentVersion', 'clusterInfo_currentVersion' - The current version of the MSK cluster.
--
-- 'encryptionInfo', 'clusterInfo_encryptionInfo' - Includes all encryption-related information.
--
-- 'enhancedMonitoring', 'clusterInfo_enhancedMonitoring' - Specifies which metrics are gathered for the MSK cluster. This property
-- has the following possible values: DEFAULT, PER_BROKER,
-- PER_TOPIC_PER_BROKER, and PER_TOPIC_PER_PARTITION. For a list of the
-- metrics associated with each of these levels of monitoring, see
-- <https://docs.aws.amazon.com/msk/latest/developerguide/monitoring.html Monitoring>.
--
-- 'loggingInfo', 'clusterInfo_loggingInfo' - Undocumented member.
--
-- 'numberOfBrokerNodes', 'clusterInfo_numberOfBrokerNodes' - The number of broker nodes in the cluster.
--
-- 'openMonitoring', 'clusterInfo_openMonitoring' - Settings for open monitoring using Prometheus.
--
-- 'state', 'clusterInfo_state' - The state of the cluster. The possible states are ACTIVE, CREATING,
-- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
--
-- 'stateInfo', 'clusterInfo_stateInfo' - Undocumented member.
--
-- 'storageMode', 'clusterInfo_storageMode' - This controls storage mode for supported storage tiers.
--
-- 'tags', 'clusterInfo_tags' - Tags attached to the cluster.
--
-- 'zookeeperConnectString', 'clusterInfo_zookeeperConnectString' - The connection string to use to connect to the Apache ZooKeeper cluster.
--
-- 'zookeeperConnectStringTls', 'clusterInfo_zookeeperConnectStringTls' - The connection string to use to connect to zookeeper cluster on Tls
-- port.
newClusterInfo ::
  ClusterInfo
newClusterInfo :: ClusterInfo
newClusterInfo =
  ClusterInfo'
    { $sel:activeOperationArn:ClusterInfo' :: Maybe Text
activeOperationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:brokerNodeGroupInfo:ClusterInfo' :: Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:clientAuthentication:ClusterInfo' :: Maybe ClientAuthentication
clientAuthentication = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterArn:ClusterInfo' :: Maybe Text
clusterArn = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterName:ClusterInfo' :: Maybe Text
clusterName = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ClusterInfo' :: Maybe ISO8601
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:currentBrokerSoftwareInfo:ClusterInfo' :: Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:currentVersion:ClusterInfo' :: Maybe Text
currentVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionInfo:ClusterInfo' :: Maybe EncryptionInfo
encryptionInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:enhancedMonitoring:ClusterInfo' :: Maybe EnhancedMonitoring
enhancedMonitoring = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingInfo:ClusterInfo' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfBrokerNodes:ClusterInfo' :: Maybe Int
numberOfBrokerNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:openMonitoring:ClusterInfo' :: Maybe OpenMonitoring
openMonitoring = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ClusterInfo' :: Maybe ClusterState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:stateInfo:ClusterInfo' :: Maybe StateInfo
stateInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:storageMode:ClusterInfo' :: Maybe StorageMode
storageMode = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ClusterInfo' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:zookeeperConnectString:ClusterInfo' :: Maybe Text
zookeeperConnectString = forall a. Maybe a
Prelude.Nothing,
      $sel:zookeeperConnectStringTls:ClusterInfo' :: Maybe Text
zookeeperConnectStringTls = forall a. Maybe a
Prelude.Nothing
    }

-- | Arn of active cluster operation.
clusterInfo_activeOperationArn :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Text)
clusterInfo_activeOperationArn :: Lens' ClusterInfo (Maybe Text)
clusterInfo_activeOperationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Text
activeOperationArn :: Maybe Text
$sel:activeOperationArn:ClusterInfo' :: ClusterInfo -> Maybe Text
activeOperationArn} -> Maybe Text
activeOperationArn) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Text
a -> ClusterInfo
s {$sel:activeOperationArn:ClusterInfo' :: Maybe Text
activeOperationArn = Maybe Text
a} :: ClusterInfo)

-- | Information about the broker nodes.
clusterInfo_brokerNodeGroupInfo :: Lens.Lens' ClusterInfo (Prelude.Maybe BrokerNodeGroupInfo)
clusterInfo_brokerNodeGroupInfo :: Lens' ClusterInfo (Maybe BrokerNodeGroupInfo)
clusterInfo_brokerNodeGroupInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo :: Maybe BrokerNodeGroupInfo
$sel:brokerNodeGroupInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo} -> Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe BrokerNodeGroupInfo
a -> ClusterInfo
s {$sel:brokerNodeGroupInfo:ClusterInfo' :: Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo = Maybe BrokerNodeGroupInfo
a} :: ClusterInfo)

-- | Includes all client authentication information.
clusterInfo_clientAuthentication :: Lens.Lens' ClusterInfo (Prelude.Maybe ClientAuthentication)
clusterInfo_clientAuthentication :: Lens' ClusterInfo (Maybe ClientAuthentication)
clusterInfo_clientAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe ClientAuthentication
clientAuthentication :: Maybe ClientAuthentication
$sel:clientAuthentication:ClusterInfo' :: ClusterInfo -> Maybe ClientAuthentication
clientAuthentication} -> Maybe ClientAuthentication
clientAuthentication) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe ClientAuthentication
a -> ClusterInfo
s {$sel:clientAuthentication:ClusterInfo' :: Maybe ClientAuthentication
clientAuthentication = Maybe ClientAuthentication
a} :: ClusterInfo)

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

-- | The name of the cluster.
clusterInfo_clusterName :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Text)
clusterInfo_clusterName :: Lens' ClusterInfo (Maybe Text)
clusterInfo_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Text
clusterName :: Maybe Text
$sel:clusterName:ClusterInfo' :: ClusterInfo -> Maybe Text
clusterName} -> Maybe Text
clusterName) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Text
a -> ClusterInfo
s {$sel:clusterName:ClusterInfo' :: Maybe Text
clusterName = Maybe Text
a} :: ClusterInfo)

-- | The time when the cluster was created.
clusterInfo_creationTime :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.UTCTime)
clusterInfo_creationTime :: Lens' ClusterInfo (Maybe UTCTime)
clusterInfo_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:ClusterInfo' :: ClusterInfo -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe ISO8601
a -> ClusterInfo
s {$sel:creationTime:ClusterInfo' :: Maybe ISO8601
creationTime = Maybe ISO8601
a} :: ClusterInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Information about the version of software currently deployed on the
-- Apache Kafka brokers in the cluster.
clusterInfo_currentBrokerSoftwareInfo :: Lens.Lens' ClusterInfo (Prelude.Maybe BrokerSoftwareInfo)
clusterInfo_currentBrokerSoftwareInfo :: Lens' ClusterInfo (Maybe BrokerSoftwareInfo)
clusterInfo_currentBrokerSoftwareInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
$sel:currentBrokerSoftwareInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo} -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe BrokerSoftwareInfo
a -> ClusterInfo
s {$sel:currentBrokerSoftwareInfo:ClusterInfo' :: Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo = Maybe BrokerSoftwareInfo
a} :: ClusterInfo)

-- | The current version of the MSK cluster.
clusterInfo_currentVersion :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Text)
clusterInfo_currentVersion :: Lens' ClusterInfo (Maybe Text)
clusterInfo_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Text
currentVersion :: Maybe Text
$sel:currentVersion:ClusterInfo' :: ClusterInfo -> Maybe Text
currentVersion} -> Maybe Text
currentVersion) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Text
a -> ClusterInfo
s {$sel:currentVersion:ClusterInfo' :: Maybe Text
currentVersion = Maybe Text
a} :: ClusterInfo)

-- | Includes all encryption-related information.
clusterInfo_encryptionInfo :: Lens.Lens' ClusterInfo (Prelude.Maybe EncryptionInfo)
clusterInfo_encryptionInfo :: Lens' ClusterInfo (Maybe EncryptionInfo)
clusterInfo_encryptionInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe EncryptionInfo
encryptionInfo :: Maybe EncryptionInfo
$sel:encryptionInfo:ClusterInfo' :: ClusterInfo -> Maybe EncryptionInfo
encryptionInfo} -> Maybe EncryptionInfo
encryptionInfo) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe EncryptionInfo
a -> ClusterInfo
s {$sel:encryptionInfo:ClusterInfo' :: Maybe EncryptionInfo
encryptionInfo = Maybe EncryptionInfo
a} :: ClusterInfo)

-- | Specifies which metrics are gathered for the MSK cluster. This property
-- has the following possible values: DEFAULT, PER_BROKER,
-- PER_TOPIC_PER_BROKER, and PER_TOPIC_PER_PARTITION. For a list of the
-- metrics associated with each of these levels of monitoring, see
-- <https://docs.aws.amazon.com/msk/latest/developerguide/monitoring.html Monitoring>.
clusterInfo_enhancedMonitoring :: Lens.Lens' ClusterInfo (Prelude.Maybe EnhancedMonitoring)
clusterInfo_enhancedMonitoring :: Lens' ClusterInfo (Maybe EnhancedMonitoring)
clusterInfo_enhancedMonitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe EnhancedMonitoring
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:enhancedMonitoring:ClusterInfo' :: ClusterInfo -> Maybe EnhancedMonitoring
enhancedMonitoring} -> Maybe EnhancedMonitoring
enhancedMonitoring) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe EnhancedMonitoring
a -> ClusterInfo
s {$sel:enhancedMonitoring:ClusterInfo' :: Maybe EnhancedMonitoring
enhancedMonitoring = Maybe EnhancedMonitoring
a} :: ClusterInfo)

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

-- | The number of broker nodes in the cluster.
clusterInfo_numberOfBrokerNodes :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Int)
clusterInfo_numberOfBrokerNodes :: Lens' ClusterInfo (Maybe Int)
clusterInfo_numberOfBrokerNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Int
numberOfBrokerNodes :: Maybe Int
$sel:numberOfBrokerNodes:ClusterInfo' :: ClusterInfo -> Maybe Int
numberOfBrokerNodes} -> Maybe Int
numberOfBrokerNodes) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Int
a -> ClusterInfo
s {$sel:numberOfBrokerNodes:ClusterInfo' :: Maybe Int
numberOfBrokerNodes = Maybe Int
a} :: ClusterInfo)

-- | Settings for open monitoring using Prometheus.
clusterInfo_openMonitoring :: Lens.Lens' ClusterInfo (Prelude.Maybe OpenMonitoring)
clusterInfo_openMonitoring :: Lens' ClusterInfo (Maybe OpenMonitoring)
clusterInfo_openMonitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe OpenMonitoring
openMonitoring :: Maybe OpenMonitoring
$sel:openMonitoring:ClusterInfo' :: ClusterInfo -> Maybe OpenMonitoring
openMonitoring} -> Maybe OpenMonitoring
openMonitoring) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe OpenMonitoring
a -> ClusterInfo
s {$sel:openMonitoring:ClusterInfo' :: Maybe OpenMonitoring
openMonitoring = Maybe OpenMonitoring
a} :: ClusterInfo)

-- | The state of the cluster. The possible states are ACTIVE, CREATING,
-- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
clusterInfo_state :: Lens.Lens' ClusterInfo (Prelude.Maybe ClusterState)
clusterInfo_state :: Lens' ClusterInfo (Maybe ClusterState)
clusterInfo_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe ClusterState
state :: Maybe ClusterState
$sel:state:ClusterInfo' :: ClusterInfo -> Maybe ClusterState
state} -> Maybe ClusterState
state) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe ClusterState
a -> ClusterInfo
s {$sel:state:ClusterInfo' :: Maybe ClusterState
state = Maybe ClusterState
a} :: ClusterInfo)

-- | Undocumented member.
clusterInfo_stateInfo :: Lens.Lens' ClusterInfo (Prelude.Maybe StateInfo)
clusterInfo_stateInfo :: Lens' ClusterInfo (Maybe StateInfo)
clusterInfo_stateInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe StateInfo
stateInfo :: Maybe StateInfo
$sel:stateInfo:ClusterInfo' :: ClusterInfo -> Maybe StateInfo
stateInfo} -> Maybe StateInfo
stateInfo) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe StateInfo
a -> ClusterInfo
s {$sel:stateInfo:ClusterInfo' :: Maybe StateInfo
stateInfo = Maybe StateInfo
a} :: ClusterInfo)

-- | This controls storage mode for supported storage tiers.
clusterInfo_storageMode :: Lens.Lens' ClusterInfo (Prelude.Maybe StorageMode)
clusterInfo_storageMode :: Lens' ClusterInfo (Maybe StorageMode)
clusterInfo_storageMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe StorageMode
storageMode :: Maybe StorageMode
$sel:storageMode:ClusterInfo' :: ClusterInfo -> Maybe StorageMode
storageMode} -> Maybe StorageMode
storageMode) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe StorageMode
a -> ClusterInfo
s {$sel:storageMode:ClusterInfo' :: Maybe StorageMode
storageMode = Maybe StorageMode
a} :: ClusterInfo)

-- | Tags attached to the cluster.
clusterInfo_tags :: Lens.Lens' ClusterInfo (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
clusterInfo_tags :: Lens' ClusterInfo (Maybe (HashMap Text Text))
clusterInfo_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ClusterInfo' :: ClusterInfo -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe (HashMap Text Text)
a -> ClusterInfo
s {$sel:tags:ClusterInfo' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ClusterInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The connection string to use to connect to the Apache ZooKeeper cluster.
clusterInfo_zookeeperConnectString :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Text)
clusterInfo_zookeeperConnectString :: Lens' ClusterInfo (Maybe Text)
clusterInfo_zookeeperConnectString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Text
zookeeperConnectString :: Maybe Text
$sel:zookeeperConnectString:ClusterInfo' :: ClusterInfo -> Maybe Text
zookeeperConnectString} -> Maybe Text
zookeeperConnectString) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Text
a -> ClusterInfo
s {$sel:zookeeperConnectString:ClusterInfo' :: Maybe Text
zookeeperConnectString = Maybe Text
a} :: ClusterInfo)

-- | The connection string to use to connect to zookeeper cluster on Tls
-- port.
clusterInfo_zookeeperConnectStringTls :: Lens.Lens' ClusterInfo (Prelude.Maybe Prelude.Text)
clusterInfo_zookeeperConnectStringTls :: Lens' ClusterInfo (Maybe Text)
clusterInfo_zookeeperConnectStringTls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterInfo' {Maybe Text
zookeeperConnectStringTls :: Maybe Text
$sel:zookeeperConnectStringTls:ClusterInfo' :: ClusterInfo -> Maybe Text
zookeeperConnectStringTls} -> Maybe Text
zookeeperConnectStringTls) (\s :: ClusterInfo
s@ClusterInfo' {} Maybe Text
a -> ClusterInfo
s {$sel:zookeeperConnectStringTls:ClusterInfo' :: Maybe Text
zookeeperConnectStringTls = Maybe Text
a} :: ClusterInfo)

instance Data.FromJSON ClusterInfo where
  parseJSON :: Value -> Parser ClusterInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ClusterInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe BrokerNodeGroupInfo
-> Maybe ClientAuthentication
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe BrokerSoftwareInfo
-> Maybe Text
-> Maybe EncryptionInfo
-> Maybe EnhancedMonitoring
-> Maybe LoggingInfo
-> Maybe Int
-> Maybe OpenMonitoring
-> Maybe ClusterState
-> Maybe StateInfo
-> Maybe StorageMode
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe Text
-> ClusterInfo
ClusterInfo'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"activeOperationArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"brokerNodeGroupInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"clientAuthentication")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"clusterName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"creationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"currentBrokerSoftwareInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"currentVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"encryptionInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"enhancedMonitoring")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"loggingInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"numberOfBrokerNodes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"openMonitoring")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"state")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"stateInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"storageMode")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"zookeeperConnectString")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"zookeeperConnectStringTls")
      )

instance Prelude.Hashable ClusterInfo where
  hashWithSalt :: Int -> ClusterInfo -> Int
hashWithSalt Int
_salt ClusterInfo' {Maybe Int
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe BrokerSoftwareInfo
Maybe ClusterState
Maybe EncryptionInfo
Maybe EnhancedMonitoring
Maybe OpenMonitoring
Maybe LoggingInfo
Maybe StateInfo
Maybe BrokerNodeGroupInfo
Maybe StorageMode
Maybe ClientAuthentication
zookeeperConnectStringTls :: Maybe Text
zookeeperConnectString :: Maybe Text
tags :: Maybe (HashMap Text Text)
storageMode :: Maybe StorageMode
stateInfo :: Maybe StateInfo
state :: Maybe ClusterState
openMonitoring :: Maybe OpenMonitoring
numberOfBrokerNodes :: Maybe Int
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
encryptionInfo :: Maybe EncryptionInfo
currentVersion :: Maybe Text
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
creationTime :: Maybe ISO8601
clusterName :: Maybe Text
clusterArn :: Maybe Text
clientAuthentication :: Maybe ClientAuthentication
brokerNodeGroupInfo :: Maybe BrokerNodeGroupInfo
activeOperationArn :: Maybe Text
$sel:zookeeperConnectStringTls:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:zookeeperConnectString:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:tags:ClusterInfo' :: ClusterInfo -> Maybe (HashMap Text Text)
$sel:storageMode:ClusterInfo' :: ClusterInfo -> Maybe StorageMode
$sel:stateInfo:ClusterInfo' :: ClusterInfo -> Maybe StateInfo
$sel:state:ClusterInfo' :: ClusterInfo -> Maybe ClusterState
$sel:openMonitoring:ClusterInfo' :: ClusterInfo -> Maybe OpenMonitoring
$sel:numberOfBrokerNodes:ClusterInfo' :: ClusterInfo -> Maybe Int
$sel:loggingInfo:ClusterInfo' :: ClusterInfo -> Maybe LoggingInfo
$sel:enhancedMonitoring:ClusterInfo' :: ClusterInfo -> Maybe EnhancedMonitoring
$sel:encryptionInfo:ClusterInfo' :: ClusterInfo -> Maybe EncryptionInfo
$sel:currentVersion:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:currentBrokerSoftwareInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerSoftwareInfo
$sel:creationTime:ClusterInfo' :: ClusterInfo -> Maybe ISO8601
$sel:clusterName:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:clusterArn:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:clientAuthentication:ClusterInfo' :: ClusterInfo -> Maybe ClientAuthentication
$sel:brokerNodeGroupInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerNodeGroupInfo
$sel:activeOperationArn:ClusterInfo' :: ClusterInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
activeOperationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClientAuthentication
clientAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionInfo
encryptionInfo
      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 Int
numberOfBrokerNodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenMonitoring
openMonitoring
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClusterState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateInfo
stateInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StorageMode
storageMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
zookeeperConnectString
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
zookeeperConnectStringTls

instance Prelude.NFData ClusterInfo where
  rnf :: ClusterInfo -> ()
rnf ClusterInfo' {Maybe Int
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe BrokerSoftwareInfo
Maybe ClusterState
Maybe EncryptionInfo
Maybe EnhancedMonitoring
Maybe OpenMonitoring
Maybe LoggingInfo
Maybe StateInfo
Maybe BrokerNodeGroupInfo
Maybe StorageMode
Maybe ClientAuthentication
zookeeperConnectStringTls :: Maybe Text
zookeeperConnectString :: Maybe Text
tags :: Maybe (HashMap Text Text)
storageMode :: Maybe StorageMode
stateInfo :: Maybe StateInfo
state :: Maybe ClusterState
openMonitoring :: Maybe OpenMonitoring
numberOfBrokerNodes :: Maybe Int
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
encryptionInfo :: Maybe EncryptionInfo
currentVersion :: Maybe Text
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
creationTime :: Maybe ISO8601
clusterName :: Maybe Text
clusterArn :: Maybe Text
clientAuthentication :: Maybe ClientAuthentication
brokerNodeGroupInfo :: Maybe BrokerNodeGroupInfo
activeOperationArn :: Maybe Text
$sel:zookeeperConnectStringTls:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:zookeeperConnectString:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:tags:ClusterInfo' :: ClusterInfo -> Maybe (HashMap Text Text)
$sel:storageMode:ClusterInfo' :: ClusterInfo -> Maybe StorageMode
$sel:stateInfo:ClusterInfo' :: ClusterInfo -> Maybe StateInfo
$sel:state:ClusterInfo' :: ClusterInfo -> Maybe ClusterState
$sel:openMonitoring:ClusterInfo' :: ClusterInfo -> Maybe OpenMonitoring
$sel:numberOfBrokerNodes:ClusterInfo' :: ClusterInfo -> Maybe Int
$sel:loggingInfo:ClusterInfo' :: ClusterInfo -> Maybe LoggingInfo
$sel:enhancedMonitoring:ClusterInfo' :: ClusterInfo -> Maybe EnhancedMonitoring
$sel:encryptionInfo:ClusterInfo' :: ClusterInfo -> Maybe EncryptionInfo
$sel:currentVersion:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:currentBrokerSoftwareInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerSoftwareInfo
$sel:creationTime:ClusterInfo' :: ClusterInfo -> Maybe ISO8601
$sel:clusterName:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:clusterArn:ClusterInfo' :: ClusterInfo -> Maybe Text
$sel:clientAuthentication:ClusterInfo' :: ClusterInfo -> Maybe ClientAuthentication
$sel:brokerNodeGroupInfo:ClusterInfo' :: ClusterInfo -> Maybe BrokerNodeGroupInfo
$sel:activeOperationArn:ClusterInfo' :: ClusterInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
activeOperationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BrokerNodeGroupInfo
brokerNodeGroupInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClientAuthentication
clientAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
clusterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
currentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionInfo
encryptionInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
numberOfBrokerNodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpenMonitoring
openMonitoring
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StateInfo
stateInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StorageMode
storageMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
zookeeperConnectString
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
zookeeperConnectStringTls