{-# 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.BrokerNodeInfo
-- 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.BrokerNodeInfo 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.BrokerSoftwareInfo
import qualified Amazonka.Prelude as Prelude

-- | BrokerNodeInfo
--
-- /See:/ 'newBrokerNodeInfo' smart constructor.
data BrokerNodeInfo = BrokerNodeInfo'
  { -- | The attached elastic network interface of the broker.
    BrokerNodeInfo -> Maybe Text
attachedENIId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the broker.
    BrokerNodeInfo -> Maybe Double
brokerId :: Prelude.Maybe Prelude.Double,
    -- | The client subnet to which this broker node belongs.
    BrokerNodeInfo -> Maybe Text
clientSubnet :: Prelude.Maybe Prelude.Text,
    -- | The virtual private cloud (VPC) of the client.
    BrokerNodeInfo -> Maybe Text
clientVpcIpAddress :: Prelude.Maybe Prelude.Text,
    -- | Information about the version of software currently deployed on the
    -- Apache Kafka brokers in the cluster.
    BrokerNodeInfo -> Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo :: Prelude.Maybe BrokerSoftwareInfo,
    -- | Endpoints for accessing the broker.
    BrokerNodeInfo -> Maybe [Text]
endpoints :: Prelude.Maybe [Prelude.Text]
  }
  deriving (BrokerNodeInfo -> BrokerNodeInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BrokerNodeInfo -> BrokerNodeInfo -> Bool
$c/= :: BrokerNodeInfo -> BrokerNodeInfo -> Bool
== :: BrokerNodeInfo -> BrokerNodeInfo -> Bool
$c== :: BrokerNodeInfo -> BrokerNodeInfo -> Bool
Prelude.Eq, ReadPrec [BrokerNodeInfo]
ReadPrec BrokerNodeInfo
Int -> ReadS BrokerNodeInfo
ReadS [BrokerNodeInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BrokerNodeInfo]
$creadListPrec :: ReadPrec [BrokerNodeInfo]
readPrec :: ReadPrec BrokerNodeInfo
$creadPrec :: ReadPrec BrokerNodeInfo
readList :: ReadS [BrokerNodeInfo]
$creadList :: ReadS [BrokerNodeInfo]
readsPrec :: Int -> ReadS BrokerNodeInfo
$creadsPrec :: Int -> ReadS BrokerNodeInfo
Prelude.Read, Int -> BrokerNodeInfo -> ShowS
[BrokerNodeInfo] -> ShowS
BrokerNodeInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BrokerNodeInfo] -> ShowS
$cshowList :: [BrokerNodeInfo] -> ShowS
show :: BrokerNodeInfo -> String
$cshow :: BrokerNodeInfo -> String
showsPrec :: Int -> BrokerNodeInfo -> ShowS
$cshowsPrec :: Int -> BrokerNodeInfo -> ShowS
Prelude.Show, forall x. Rep BrokerNodeInfo x -> BrokerNodeInfo
forall x. BrokerNodeInfo -> Rep BrokerNodeInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BrokerNodeInfo x -> BrokerNodeInfo
$cfrom :: forall x. BrokerNodeInfo -> Rep BrokerNodeInfo x
Prelude.Generic)

-- |
-- Create a value of 'BrokerNodeInfo' 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:
--
-- 'attachedENIId', 'brokerNodeInfo_attachedENIId' - The attached elastic network interface of the broker.
--
-- 'brokerId', 'brokerNodeInfo_brokerId' - The ID of the broker.
--
-- 'clientSubnet', 'brokerNodeInfo_clientSubnet' - The client subnet to which this broker node belongs.
--
-- 'clientVpcIpAddress', 'brokerNodeInfo_clientVpcIpAddress' - The virtual private cloud (VPC) of the client.
--
-- 'currentBrokerSoftwareInfo', 'brokerNodeInfo_currentBrokerSoftwareInfo' - Information about the version of software currently deployed on the
-- Apache Kafka brokers in the cluster.
--
-- 'endpoints', 'brokerNodeInfo_endpoints' - Endpoints for accessing the broker.
newBrokerNodeInfo ::
  BrokerNodeInfo
newBrokerNodeInfo :: BrokerNodeInfo
newBrokerNodeInfo =
  BrokerNodeInfo'
    { $sel:attachedENIId:BrokerNodeInfo' :: Maybe Text
attachedENIId = forall a. Maybe a
Prelude.Nothing,
      $sel:brokerId:BrokerNodeInfo' :: Maybe Double
brokerId = forall a. Maybe a
Prelude.Nothing,
      $sel:clientSubnet:BrokerNodeInfo' :: Maybe Text
clientSubnet = forall a. Maybe a
Prelude.Nothing,
      $sel:clientVpcIpAddress:BrokerNodeInfo' :: Maybe Text
clientVpcIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:currentBrokerSoftwareInfo:BrokerNodeInfo' :: Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:endpoints:BrokerNodeInfo' :: Maybe [Text]
endpoints = forall a. Maybe a
Prelude.Nothing
    }

-- | The attached elastic network interface of the broker.
brokerNodeInfo_attachedENIId :: Lens.Lens' BrokerNodeInfo (Prelude.Maybe Prelude.Text)
brokerNodeInfo_attachedENIId :: Lens' BrokerNodeInfo (Maybe Text)
brokerNodeInfo_attachedENIId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BrokerNodeInfo' {Maybe Text
attachedENIId :: Maybe Text
$sel:attachedENIId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
attachedENIId} -> Maybe Text
attachedENIId) (\s :: BrokerNodeInfo
s@BrokerNodeInfo' {} Maybe Text
a -> BrokerNodeInfo
s {$sel:attachedENIId:BrokerNodeInfo' :: Maybe Text
attachedENIId = Maybe Text
a} :: BrokerNodeInfo)

-- | The ID of the broker.
brokerNodeInfo_brokerId :: Lens.Lens' BrokerNodeInfo (Prelude.Maybe Prelude.Double)
brokerNodeInfo_brokerId :: Lens' BrokerNodeInfo (Maybe Double)
brokerNodeInfo_brokerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BrokerNodeInfo' {Maybe Double
brokerId :: Maybe Double
$sel:brokerId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Double
brokerId} -> Maybe Double
brokerId) (\s :: BrokerNodeInfo
s@BrokerNodeInfo' {} Maybe Double
a -> BrokerNodeInfo
s {$sel:brokerId:BrokerNodeInfo' :: Maybe Double
brokerId = Maybe Double
a} :: BrokerNodeInfo)

-- | The client subnet to which this broker node belongs.
brokerNodeInfo_clientSubnet :: Lens.Lens' BrokerNodeInfo (Prelude.Maybe Prelude.Text)
brokerNodeInfo_clientSubnet :: Lens' BrokerNodeInfo (Maybe Text)
brokerNodeInfo_clientSubnet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BrokerNodeInfo' {Maybe Text
clientSubnet :: Maybe Text
$sel:clientSubnet:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
clientSubnet} -> Maybe Text
clientSubnet) (\s :: BrokerNodeInfo
s@BrokerNodeInfo' {} Maybe Text
a -> BrokerNodeInfo
s {$sel:clientSubnet:BrokerNodeInfo' :: Maybe Text
clientSubnet = Maybe Text
a} :: BrokerNodeInfo)

-- | The virtual private cloud (VPC) of the client.
brokerNodeInfo_clientVpcIpAddress :: Lens.Lens' BrokerNodeInfo (Prelude.Maybe Prelude.Text)
brokerNodeInfo_clientVpcIpAddress :: Lens' BrokerNodeInfo (Maybe Text)
brokerNodeInfo_clientVpcIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BrokerNodeInfo' {Maybe Text
clientVpcIpAddress :: Maybe Text
$sel:clientVpcIpAddress:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
clientVpcIpAddress} -> Maybe Text
clientVpcIpAddress) (\s :: BrokerNodeInfo
s@BrokerNodeInfo' {} Maybe Text
a -> BrokerNodeInfo
s {$sel:clientVpcIpAddress:BrokerNodeInfo' :: Maybe Text
clientVpcIpAddress = Maybe Text
a} :: BrokerNodeInfo)

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

-- | Endpoints for accessing the broker.
brokerNodeInfo_endpoints :: Lens.Lens' BrokerNodeInfo (Prelude.Maybe [Prelude.Text])
brokerNodeInfo_endpoints :: Lens' BrokerNodeInfo (Maybe [Text])
brokerNodeInfo_endpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BrokerNodeInfo' {Maybe [Text]
endpoints :: Maybe [Text]
$sel:endpoints:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe [Text]
endpoints} -> Maybe [Text]
endpoints) (\s :: BrokerNodeInfo
s@BrokerNodeInfo' {} Maybe [Text]
a -> BrokerNodeInfo
s {$sel:endpoints:BrokerNodeInfo' :: Maybe [Text]
endpoints = Maybe [Text]
a} :: BrokerNodeInfo) 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

instance Data.FromJSON BrokerNodeInfo where
  parseJSON :: Value -> Parser BrokerNodeInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"BrokerNodeInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe Double
-> Maybe Text
-> Maybe Text
-> Maybe BrokerSoftwareInfo
-> Maybe [Text]
-> BrokerNodeInfo
BrokerNodeInfo'
            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
"attachedENIId")
            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
"brokerId")
            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
"clientSubnet")
            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
"clientVpcIpAddress")
            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
"endpoints" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable BrokerNodeInfo where
  hashWithSalt :: Int -> BrokerNodeInfo -> Int
hashWithSalt Int
_salt BrokerNodeInfo' {Maybe Double
Maybe [Text]
Maybe Text
Maybe BrokerSoftwareInfo
endpoints :: Maybe [Text]
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
clientVpcIpAddress :: Maybe Text
clientSubnet :: Maybe Text
brokerId :: Maybe Double
attachedENIId :: Maybe Text
$sel:endpoints:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe [Text]
$sel:currentBrokerSoftwareInfo:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe BrokerSoftwareInfo
$sel:clientVpcIpAddress:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
$sel:clientSubnet:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
$sel:brokerId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Double
$sel:attachedENIId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
attachedENIId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
brokerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientSubnet
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientVpcIpAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BrokerSoftwareInfo
currentBrokerSoftwareInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
endpoints

instance Prelude.NFData BrokerNodeInfo where
  rnf :: BrokerNodeInfo -> ()
rnf BrokerNodeInfo' {Maybe Double
Maybe [Text]
Maybe Text
Maybe BrokerSoftwareInfo
endpoints :: Maybe [Text]
currentBrokerSoftwareInfo :: Maybe BrokerSoftwareInfo
clientVpcIpAddress :: Maybe Text
clientSubnet :: Maybe Text
brokerId :: Maybe Double
attachedENIId :: Maybe Text
$sel:endpoints:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe [Text]
$sel:currentBrokerSoftwareInfo:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe BrokerSoftwareInfo
$sel:clientVpcIpAddress:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
$sel:clientSubnet:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
$sel:brokerId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Double
$sel:attachedENIId:BrokerNodeInfo' :: BrokerNodeInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attachedENIId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
brokerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientSubnet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientVpcIpAddress
      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]
endpoints