{-# 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.Provisioned
-- 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.Provisioned 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.EncryptionInfo
import Amazonka.Kafka.Types.EnhancedMonitoring
import Amazonka.Kafka.Types.LoggingInfo
import Amazonka.Kafka.Types.OpenMonitoringInfo
import Amazonka.Kafka.Types.StorageMode
import qualified Amazonka.Prelude as Prelude

-- | Provisioned cluster.
--
-- /See:/ 'newProvisioned' smart constructor.
data Provisioned = Provisioned'
  { -- | Includes all client authentication information.
    Provisioned -> Maybe ClientAuthentication
clientAuthentication :: Prelude.Maybe ClientAuthentication,
    -- | Information about the Apache Kafka version deployed on the brokers.
    Provisioned -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo :: Prelude.Maybe BrokerSoftwareInfo,
    -- | Includes all encryption-related information.
    Provisioned -> Maybe EncryptionInfo
encryptionInfo :: Prelude.Maybe EncryptionInfo,
    -- | Specifies the level of monitoring for the MSK cluster. The possible
    -- values are DEFAULT, PER_BROKER, PER_TOPIC_PER_BROKER, and
    -- PER_TOPIC_PER_PARTITION.
    Provisioned -> Maybe EnhancedMonitoring
enhancedMonitoring :: Prelude.Maybe EnhancedMonitoring,
    -- | Log delivery information for the cluster.
    Provisioned -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The settings for open monitoring.
    Provisioned -> Maybe OpenMonitoringInfo
openMonitoring :: Prelude.Maybe OpenMonitoringInfo,
    -- | This controls storage mode for supported storage tiers.
    Provisioned -> Maybe StorageMode
storageMode :: Prelude.Maybe StorageMode,
    -- | The connection string to use to connect to the Apache ZooKeeper cluster.
    Provisioned -> Maybe Text
zookeeperConnectString :: Prelude.Maybe Prelude.Text,
    -- | The connection string to use to connect to the Apache ZooKeeper cluster
    -- on a TLS port.
    Provisioned -> Maybe Text
zookeeperConnectStringTls :: Prelude.Maybe Prelude.Text,
    -- | Information about the brokers.
    Provisioned -> BrokerNodeGroupInfo
brokerNodeGroupInfo :: BrokerNodeGroupInfo,
    -- | The number of broker nodes in the cluster.
    Provisioned -> Natural
numberOfBrokerNodes :: Prelude.Natural
  }
  deriving (Provisioned -> Provisioned -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Provisioned -> Provisioned -> Bool
$c/= :: Provisioned -> Provisioned -> Bool
== :: Provisioned -> Provisioned -> Bool
$c== :: Provisioned -> Provisioned -> Bool
Prelude.Eq, ReadPrec [Provisioned]
ReadPrec Provisioned
Int -> ReadS Provisioned
ReadS [Provisioned]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Provisioned]
$creadListPrec :: ReadPrec [Provisioned]
readPrec :: ReadPrec Provisioned
$creadPrec :: ReadPrec Provisioned
readList :: ReadS [Provisioned]
$creadList :: ReadS [Provisioned]
readsPrec :: Int -> ReadS Provisioned
$creadsPrec :: Int -> ReadS Provisioned
Prelude.Read, Int -> Provisioned -> ShowS
[Provisioned] -> ShowS
Provisioned -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Provisioned] -> ShowS
$cshowList :: [Provisioned] -> ShowS
show :: Provisioned -> String
$cshow :: Provisioned -> String
showsPrec :: Int -> Provisioned -> ShowS
$cshowsPrec :: Int -> Provisioned -> ShowS
Prelude.Show, forall x. Rep Provisioned x -> Provisioned
forall x. Provisioned -> Rep Provisioned x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Provisioned x -> Provisioned
$cfrom :: forall x. Provisioned -> Rep Provisioned x
Prelude.Generic)

-- |
-- Create a value of 'Provisioned' 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:
--
-- 'clientAuthentication', 'provisioned_clientAuthentication' - Includes all client authentication information.
--
-- 'currentBrokerSoftwareInfo', 'provisioned_currentBrokerSoftwareInfo' - Information about the Apache Kafka version deployed on the brokers.
--
-- 'encryptionInfo', 'provisioned_encryptionInfo' - Includes all encryption-related information.
--
-- 'enhancedMonitoring', 'provisioned_enhancedMonitoring' - Specifies the level of monitoring for the MSK cluster. The possible
-- values are DEFAULT, PER_BROKER, PER_TOPIC_PER_BROKER, and
-- PER_TOPIC_PER_PARTITION.
--
-- 'loggingInfo', 'provisioned_loggingInfo' - Log delivery information for the cluster.
--
-- 'openMonitoring', 'provisioned_openMonitoring' - The settings for open monitoring.
--
-- 'storageMode', 'provisioned_storageMode' - This controls storage mode for supported storage tiers.
--
-- 'zookeeperConnectString', 'provisioned_zookeeperConnectString' - The connection string to use to connect to the Apache ZooKeeper cluster.
--
-- 'zookeeperConnectStringTls', 'provisioned_zookeeperConnectStringTls' - The connection string to use to connect to the Apache ZooKeeper cluster
-- on a TLS port.
--
-- 'brokerNodeGroupInfo', 'provisioned_brokerNodeGroupInfo' - Information about the brokers.
--
-- 'numberOfBrokerNodes', 'provisioned_numberOfBrokerNodes' - The number of broker nodes in the cluster.
newProvisioned ::
  -- | 'brokerNodeGroupInfo'
  BrokerNodeGroupInfo ->
  -- | 'numberOfBrokerNodes'
  Prelude.Natural ->
  Provisioned
newProvisioned :: BrokerNodeGroupInfo -> Natural -> Provisioned
newProvisioned
  BrokerNodeGroupInfo
pBrokerNodeGroupInfo_
  Natural
pNumberOfBrokerNodes_ =
    Provisioned'
      { $sel:clientAuthentication:Provisioned' :: Maybe ClientAuthentication
clientAuthentication =
          forall a. Maybe a
Prelude.Nothing,
        $sel:currentBrokerSoftwareInfo:Provisioned' :: Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo = forall a. Maybe a
Prelude.Nothing,
        $sel:encryptionInfo:Provisioned' :: Maybe EncryptionInfo
encryptionInfo = forall a. Maybe a
Prelude.Nothing,
        $sel:enhancedMonitoring:Provisioned' :: Maybe EnhancedMonitoring
enhancedMonitoring = forall a. Maybe a
Prelude.Nothing,
        $sel:loggingInfo:Provisioned' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
        $sel:openMonitoring:Provisioned' :: Maybe OpenMonitoringInfo
openMonitoring = forall a. Maybe a
Prelude.Nothing,
        $sel:storageMode:Provisioned' :: Maybe StorageMode
storageMode = forall a. Maybe a
Prelude.Nothing,
        $sel:zookeeperConnectString:Provisioned' :: Maybe Text
zookeeperConnectString = forall a. Maybe a
Prelude.Nothing,
        $sel:zookeeperConnectStringTls:Provisioned' :: Maybe Text
zookeeperConnectStringTls = forall a. Maybe a
Prelude.Nothing,
        $sel:brokerNodeGroupInfo:Provisioned' :: BrokerNodeGroupInfo
brokerNodeGroupInfo = BrokerNodeGroupInfo
pBrokerNodeGroupInfo_,
        $sel:numberOfBrokerNodes:Provisioned' :: Natural
numberOfBrokerNodes = Natural
pNumberOfBrokerNodes_
      }

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

-- | Information about the Apache Kafka version deployed on the brokers.
provisioned_currentBrokerSoftwareInfo :: Lens.Lens' Provisioned (Prelude.Maybe BrokerSoftwareInfo)
provisioned_currentBrokerSoftwareInfo :: Lens' Provisioned (Maybe BrokerSoftwareInfo)
provisioned_currentBrokerSoftwareInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Provisioned' {Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
$sel:currentBrokerSoftwareInfo:Provisioned' :: Provisioned -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo} -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo) (\s :: Provisioned
s@Provisioned' {} Maybe BrokerSoftwareInfo
a -> Provisioned
s {$sel:currentBrokerSoftwareInfo:Provisioned' :: Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo = Maybe BrokerSoftwareInfo
a} :: Provisioned)

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

-- | Specifies the level of monitoring for the MSK cluster. The possible
-- values are DEFAULT, PER_BROKER, PER_TOPIC_PER_BROKER, and
-- PER_TOPIC_PER_PARTITION.
provisioned_enhancedMonitoring :: Lens.Lens' Provisioned (Prelude.Maybe EnhancedMonitoring)
provisioned_enhancedMonitoring :: Lens' Provisioned (Maybe EnhancedMonitoring)
provisioned_enhancedMonitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Provisioned' {Maybe EnhancedMonitoring
enhancedMonitoring :: Maybe EnhancedMonitoring
$sel:enhancedMonitoring:Provisioned' :: Provisioned -> Maybe EnhancedMonitoring
enhancedMonitoring} -> Maybe EnhancedMonitoring
enhancedMonitoring) (\s :: Provisioned
s@Provisioned' {} Maybe EnhancedMonitoring
a -> Provisioned
s {$sel:enhancedMonitoring:Provisioned' :: Maybe EnhancedMonitoring
enhancedMonitoring = Maybe EnhancedMonitoring
a} :: Provisioned)

-- | Log delivery information for the cluster.
provisioned_loggingInfo :: Lens.Lens' Provisioned (Prelude.Maybe LoggingInfo)
provisioned_loggingInfo :: Lens' Provisioned (Maybe LoggingInfo)
provisioned_loggingInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Provisioned' {Maybe LoggingInfo
loggingInfo :: Maybe LoggingInfo
$sel:loggingInfo:Provisioned' :: Provisioned -> Maybe LoggingInfo
loggingInfo} -> Maybe LoggingInfo
loggingInfo) (\s :: Provisioned
s@Provisioned' {} Maybe LoggingInfo
a -> Provisioned
s {$sel:loggingInfo:Provisioned' :: Maybe LoggingInfo
loggingInfo = Maybe LoggingInfo
a} :: Provisioned)

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

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

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

-- | The connection string to use to connect to the Apache ZooKeeper cluster
-- on a TLS port.
provisioned_zookeeperConnectStringTls :: Lens.Lens' Provisioned (Prelude.Maybe Prelude.Text)
provisioned_zookeeperConnectStringTls :: Lens' Provisioned (Maybe Text)
provisioned_zookeeperConnectStringTls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Provisioned' {Maybe Text
zookeeperConnectStringTls :: Maybe Text
$sel:zookeeperConnectStringTls:Provisioned' :: Provisioned -> Maybe Text
zookeeperConnectStringTls} -> Maybe Text
zookeeperConnectStringTls) (\s :: Provisioned
s@Provisioned' {} Maybe Text
a -> Provisioned
s {$sel:zookeeperConnectStringTls:Provisioned' :: Maybe Text
zookeeperConnectStringTls = Maybe Text
a} :: Provisioned)

-- | Information about the brokers.
provisioned_brokerNodeGroupInfo :: Lens.Lens' Provisioned BrokerNodeGroupInfo
provisioned_brokerNodeGroupInfo :: Lens' Provisioned BrokerNodeGroupInfo
provisioned_brokerNodeGroupInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Provisioned' {BrokerNodeGroupInfo
brokerNodeGroupInfo :: BrokerNodeGroupInfo
$sel:brokerNodeGroupInfo:Provisioned' :: Provisioned -> BrokerNodeGroupInfo
brokerNodeGroupInfo} -> BrokerNodeGroupInfo
brokerNodeGroupInfo) (\s :: Provisioned
s@Provisioned' {} BrokerNodeGroupInfo
a -> Provisioned
s {$sel:brokerNodeGroupInfo:Provisioned' :: BrokerNodeGroupInfo
brokerNodeGroupInfo = BrokerNodeGroupInfo
a} :: Provisioned)

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

instance Data.FromJSON Provisioned where
  parseJSON :: Value -> Parser Provisioned
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Provisioned"
      ( \Object
x ->
          Maybe ClientAuthentication
-> Maybe BrokerSoftwareInfo
-> Maybe EncryptionInfo
-> Maybe EnhancedMonitoring
-> Maybe LoggingInfo
-> Maybe OpenMonitoringInfo
-> Maybe StorageMode
-> Maybe Text
-> Maybe Text
-> BrokerNodeGroupInfo
-> Natural
-> Provisioned
Provisioned'
            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
"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
"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
"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
"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
"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
"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")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"numberOfBrokerNodes")
      )

instance Prelude.Hashable Provisioned where
  hashWithSalt :: Int -> Provisioned -> Int
hashWithSalt Int
_salt Provisioned' {Natural
Maybe Text
Maybe BrokerSoftwareInfo
Maybe EncryptionInfo
Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Maybe StorageMode
Maybe ClientAuthentication
BrokerNodeGroupInfo
numberOfBrokerNodes :: Natural
brokerNodeGroupInfo :: BrokerNodeGroupInfo
zookeeperConnectStringTls :: Maybe Text
zookeeperConnectString :: Maybe Text
storageMode :: Maybe StorageMode
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
encryptionInfo :: Maybe EncryptionInfo
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:numberOfBrokerNodes:Provisioned' :: Provisioned -> Natural
$sel:brokerNodeGroupInfo:Provisioned' :: Provisioned -> BrokerNodeGroupInfo
$sel:zookeeperConnectStringTls:Provisioned' :: Provisioned -> Maybe Text
$sel:zookeeperConnectString:Provisioned' :: Provisioned -> Maybe Text
$sel:storageMode:Provisioned' :: Provisioned -> Maybe StorageMode
$sel:openMonitoring:Provisioned' :: Provisioned -> Maybe OpenMonitoringInfo
$sel:loggingInfo:Provisioned' :: Provisioned -> Maybe LoggingInfo
$sel:enhancedMonitoring:Provisioned' :: Provisioned -> Maybe EnhancedMonitoring
$sel:encryptionInfo:Provisioned' :: Provisioned -> Maybe EncryptionInfo
$sel:currentBrokerSoftwareInfo:Provisioned' :: Provisioned -> Maybe BrokerSoftwareInfo
$sel:clientAuthentication:Provisioned' :: Provisioned -> Maybe ClientAuthentication
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClientAuthentication
clientAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo
      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 OpenMonitoringInfo
openMonitoring
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StorageMode
storageMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
zookeeperConnectString
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
zookeeperConnectStringTls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BrokerNodeGroupInfo
brokerNodeGroupInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
numberOfBrokerNodes

instance Prelude.NFData Provisioned where
  rnf :: Provisioned -> ()
rnf Provisioned' {Natural
Maybe Text
Maybe BrokerSoftwareInfo
Maybe EncryptionInfo
Maybe EnhancedMonitoring
Maybe OpenMonitoringInfo
Maybe LoggingInfo
Maybe StorageMode
Maybe ClientAuthentication
BrokerNodeGroupInfo
numberOfBrokerNodes :: Natural
brokerNodeGroupInfo :: BrokerNodeGroupInfo
zookeeperConnectStringTls :: Maybe Text
zookeeperConnectString :: Maybe Text
storageMode :: Maybe StorageMode
openMonitoring :: Maybe OpenMonitoringInfo
loggingInfo :: Maybe LoggingInfo
enhancedMonitoring :: Maybe EnhancedMonitoring
encryptionInfo :: Maybe EncryptionInfo
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:numberOfBrokerNodes:Provisioned' :: Provisioned -> Natural
$sel:brokerNodeGroupInfo:Provisioned' :: Provisioned -> BrokerNodeGroupInfo
$sel:zookeeperConnectStringTls:Provisioned' :: Provisioned -> Maybe Text
$sel:zookeeperConnectString:Provisioned' :: Provisioned -> Maybe Text
$sel:storageMode:Provisioned' :: Provisioned -> Maybe StorageMode
$sel:openMonitoring:Provisioned' :: Provisioned -> Maybe OpenMonitoringInfo
$sel:loggingInfo:Provisioned' :: Provisioned -> Maybe LoggingInfo
$sel:enhancedMonitoring:Provisioned' :: Provisioned -> Maybe EnhancedMonitoring
$sel:encryptionInfo:Provisioned' :: Provisioned -> Maybe EncryptionInfo
$sel:currentBrokerSoftwareInfo:Provisioned' :: Provisioned -> Maybe BrokerSoftwareInfo
$sel:clientAuthentication:Provisioned' :: Provisioned -> Maybe ClientAuthentication
..} =
    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 BrokerSoftwareInfo
currentBrokerSoftwareInfo
      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 OpenMonitoringInfo
openMonitoring
      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 Text
zookeeperConnectString
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
zookeeperConnectStringTls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BrokerNodeGroupInfo
brokerNodeGroupInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
numberOfBrokerNodes