{-# 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.KafkaConnect.Types.ConnectorSummary
-- 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.KafkaConnect.Types.ConnectorSummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KafkaConnect.Types.CapacityDescription
import Amazonka.KafkaConnect.Types.ConnectorState
import Amazonka.KafkaConnect.Types.KafkaClusterClientAuthenticationDescription
import Amazonka.KafkaConnect.Types.KafkaClusterDescription
import Amazonka.KafkaConnect.Types.KafkaClusterEncryptionInTransitDescription
import Amazonka.KafkaConnect.Types.LogDeliveryDescription
import Amazonka.KafkaConnect.Types.PluginDescription
import Amazonka.KafkaConnect.Types.WorkerConfigurationDescription
import qualified Amazonka.Prelude as Prelude

-- | Summary of a connector.
--
-- /See:/ 'newConnectorSummary' smart constructor.
data ConnectorSummary = ConnectorSummary'
  { -- | The connector\'s compute capacity settings.
    ConnectorSummary -> Maybe CapacityDescription
capacity :: Prelude.Maybe CapacityDescription,
    -- | The Amazon Resource Name (ARN) of the connector.
    ConnectorSummary -> Maybe Text
connectorArn :: Prelude.Maybe Prelude.Text,
    -- | The description of the connector.
    ConnectorSummary -> Maybe Text
connectorDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the connector.
    ConnectorSummary -> Maybe Text
connectorName :: Prelude.Maybe Prelude.Text,
    -- | The state of the connector.
    ConnectorSummary -> Maybe ConnectorState
connectorState :: Prelude.Maybe ConnectorState,
    -- | The time that the connector was created.
    ConnectorSummary -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | The current version of the connector.
    ConnectorSummary -> Maybe Text
currentVersion :: Prelude.Maybe Prelude.Text,
    -- | The details of the Apache Kafka cluster to which the connector is
    -- connected.
    ConnectorSummary -> Maybe KafkaClusterDescription
kafkaCluster :: Prelude.Maybe KafkaClusterDescription,
    -- | The type of client authentication used to connect to the Apache Kafka
    -- cluster. The value is NONE when no client authentication is used.
    ConnectorSummary
-> Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication :: Prelude.Maybe KafkaClusterClientAuthenticationDescription,
    -- | Details of encryption in transit to the Apache Kafka cluster.
    ConnectorSummary
-> Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit :: Prelude.Maybe KafkaClusterEncryptionInTransitDescription,
    -- | The version of Kafka Connect. It has to be compatible with both the
    -- Apache Kafka cluster\'s version and the plugins.
    ConnectorSummary -> Maybe Text
kafkaConnectVersion :: Prelude.Maybe Prelude.Text,
    -- | The settings for delivering connector logs to Amazon CloudWatch Logs.
    ConnectorSummary -> Maybe LogDeliveryDescription
logDelivery :: Prelude.Maybe LogDeliveryDescription,
    -- | Specifies which plugins were used for this connector.
    ConnectorSummary -> Maybe [PluginDescription]
plugins :: Prelude.Maybe [PluginDescription],
    -- | The Amazon Resource Name (ARN) of the IAM role used by the connector to
    -- access Amazon Web Services resources.
    ConnectorSummary -> Maybe Text
serviceExecutionRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The worker configurations that are in use with the connector.
    ConnectorSummary -> Maybe WorkerConfigurationDescription
workerConfiguration :: Prelude.Maybe WorkerConfigurationDescription
  }
  deriving (ConnectorSummary -> ConnectorSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectorSummary -> ConnectorSummary -> Bool
$c/= :: ConnectorSummary -> ConnectorSummary -> Bool
== :: ConnectorSummary -> ConnectorSummary -> Bool
$c== :: ConnectorSummary -> ConnectorSummary -> Bool
Prelude.Eq, ReadPrec [ConnectorSummary]
ReadPrec ConnectorSummary
Int -> ReadS ConnectorSummary
ReadS [ConnectorSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConnectorSummary]
$creadListPrec :: ReadPrec [ConnectorSummary]
readPrec :: ReadPrec ConnectorSummary
$creadPrec :: ReadPrec ConnectorSummary
readList :: ReadS [ConnectorSummary]
$creadList :: ReadS [ConnectorSummary]
readsPrec :: Int -> ReadS ConnectorSummary
$creadsPrec :: Int -> ReadS ConnectorSummary
Prelude.Read, Int -> ConnectorSummary -> ShowS
[ConnectorSummary] -> ShowS
ConnectorSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectorSummary] -> ShowS
$cshowList :: [ConnectorSummary] -> ShowS
show :: ConnectorSummary -> String
$cshow :: ConnectorSummary -> String
showsPrec :: Int -> ConnectorSummary -> ShowS
$cshowsPrec :: Int -> ConnectorSummary -> ShowS
Prelude.Show, forall x. Rep ConnectorSummary x -> ConnectorSummary
forall x. ConnectorSummary -> Rep ConnectorSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectorSummary x -> ConnectorSummary
$cfrom :: forall x. ConnectorSummary -> Rep ConnectorSummary x
Prelude.Generic)

-- |
-- Create a value of 'ConnectorSummary' 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:
--
-- 'capacity', 'connectorSummary_capacity' - The connector\'s compute capacity settings.
--
-- 'connectorArn', 'connectorSummary_connectorArn' - The Amazon Resource Name (ARN) of the connector.
--
-- 'connectorDescription', 'connectorSummary_connectorDescription' - The description of the connector.
--
-- 'connectorName', 'connectorSummary_connectorName' - The name of the connector.
--
-- 'connectorState', 'connectorSummary_connectorState' - The state of the connector.
--
-- 'creationTime', 'connectorSummary_creationTime' - The time that the connector was created.
--
-- 'currentVersion', 'connectorSummary_currentVersion' - The current version of the connector.
--
-- 'kafkaCluster', 'connectorSummary_kafkaCluster' - The details of the Apache Kafka cluster to which the connector is
-- connected.
--
-- 'kafkaClusterClientAuthentication', 'connectorSummary_kafkaClusterClientAuthentication' - The type of client authentication used to connect to the Apache Kafka
-- cluster. The value is NONE when no client authentication is used.
--
-- 'kafkaClusterEncryptionInTransit', 'connectorSummary_kafkaClusterEncryptionInTransit' - Details of encryption in transit to the Apache Kafka cluster.
--
-- 'kafkaConnectVersion', 'connectorSummary_kafkaConnectVersion' - The version of Kafka Connect. It has to be compatible with both the
-- Apache Kafka cluster\'s version and the plugins.
--
-- 'logDelivery', 'connectorSummary_logDelivery' - The settings for delivering connector logs to Amazon CloudWatch Logs.
--
-- 'plugins', 'connectorSummary_plugins' - Specifies which plugins were used for this connector.
--
-- 'serviceExecutionRoleArn', 'connectorSummary_serviceExecutionRoleArn' - The Amazon Resource Name (ARN) of the IAM role used by the connector to
-- access Amazon Web Services resources.
--
-- 'workerConfiguration', 'connectorSummary_workerConfiguration' - The worker configurations that are in use with the connector.
newConnectorSummary ::
  ConnectorSummary
newConnectorSummary :: ConnectorSummary
newConnectorSummary =
  ConnectorSummary'
    { $sel:capacity:ConnectorSummary' :: Maybe CapacityDescription
capacity = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorArn:ConnectorSummary' :: Maybe Text
connectorArn = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorDescription:ConnectorSummary' :: Maybe Text
connectorDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorName:ConnectorSummary' :: Maybe Text
connectorName = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorState:ConnectorSummary' :: Maybe ConnectorState
connectorState = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ConnectorSummary' :: Maybe ISO8601
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:currentVersion:ConnectorSummary' :: Maybe Text
currentVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:kafkaCluster:ConnectorSummary' :: Maybe KafkaClusterDescription
kafkaCluster = forall a. Maybe a
Prelude.Nothing,
      $sel:kafkaClusterClientAuthentication:ConnectorSummary' :: Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication = forall a. Maybe a
Prelude.Nothing,
      $sel:kafkaClusterEncryptionInTransit:ConnectorSummary' :: Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit = forall a. Maybe a
Prelude.Nothing,
      $sel:kafkaConnectVersion:ConnectorSummary' :: Maybe Text
kafkaConnectVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:logDelivery:ConnectorSummary' :: Maybe LogDeliveryDescription
logDelivery = forall a. Maybe a
Prelude.Nothing,
      $sel:plugins:ConnectorSummary' :: Maybe [PluginDescription]
plugins = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceExecutionRoleArn:ConnectorSummary' :: Maybe Text
serviceExecutionRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:workerConfiguration:ConnectorSummary' :: Maybe WorkerConfigurationDescription
workerConfiguration = forall a. Maybe a
Prelude.Nothing
    }

-- | The connector\'s compute capacity settings.
connectorSummary_capacity :: Lens.Lens' ConnectorSummary (Prelude.Maybe CapacityDescription)
connectorSummary_capacity :: Lens' ConnectorSummary (Maybe CapacityDescription)
connectorSummary_capacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe CapacityDescription
capacity :: Maybe CapacityDescription
$sel:capacity:ConnectorSummary' :: ConnectorSummary -> Maybe CapacityDescription
capacity} -> Maybe CapacityDescription
capacity) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe CapacityDescription
a -> ConnectorSummary
s {$sel:capacity:ConnectorSummary' :: Maybe CapacityDescription
capacity = Maybe CapacityDescription
a} :: ConnectorSummary)

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

-- | The description of the connector.
connectorSummary_connectorDescription :: Lens.Lens' ConnectorSummary (Prelude.Maybe Prelude.Text)
connectorSummary_connectorDescription :: Lens' ConnectorSummary (Maybe Text)
connectorSummary_connectorDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe Text
connectorDescription :: Maybe Text
$sel:connectorDescription:ConnectorSummary' :: ConnectorSummary -> Maybe Text
connectorDescription} -> Maybe Text
connectorDescription) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe Text
a -> ConnectorSummary
s {$sel:connectorDescription:ConnectorSummary' :: Maybe Text
connectorDescription = Maybe Text
a} :: ConnectorSummary)

-- | The name of the connector.
connectorSummary_connectorName :: Lens.Lens' ConnectorSummary (Prelude.Maybe Prelude.Text)
connectorSummary_connectorName :: Lens' ConnectorSummary (Maybe Text)
connectorSummary_connectorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe Text
connectorName :: Maybe Text
$sel:connectorName:ConnectorSummary' :: ConnectorSummary -> Maybe Text
connectorName} -> Maybe Text
connectorName) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe Text
a -> ConnectorSummary
s {$sel:connectorName:ConnectorSummary' :: Maybe Text
connectorName = Maybe Text
a} :: ConnectorSummary)

-- | The state of the connector.
connectorSummary_connectorState :: Lens.Lens' ConnectorSummary (Prelude.Maybe ConnectorState)
connectorSummary_connectorState :: Lens' ConnectorSummary (Maybe ConnectorState)
connectorSummary_connectorState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe ConnectorState
connectorState :: Maybe ConnectorState
$sel:connectorState:ConnectorSummary' :: ConnectorSummary -> Maybe ConnectorState
connectorState} -> Maybe ConnectorState
connectorState) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe ConnectorState
a -> ConnectorSummary
s {$sel:connectorState:ConnectorSummary' :: Maybe ConnectorState
connectorState = Maybe ConnectorState
a} :: ConnectorSummary)

-- | The time that the connector was created.
connectorSummary_creationTime :: Lens.Lens' ConnectorSummary (Prelude.Maybe Prelude.UTCTime)
connectorSummary_creationTime :: Lens' ConnectorSummary (Maybe UTCTime)
connectorSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:ConnectorSummary' :: ConnectorSummary -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe ISO8601
a -> ConnectorSummary
s {$sel:creationTime:ConnectorSummary' :: Maybe ISO8601
creationTime = Maybe ISO8601
a} :: ConnectorSummary) 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

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

-- | The details of the Apache Kafka cluster to which the connector is
-- connected.
connectorSummary_kafkaCluster :: Lens.Lens' ConnectorSummary (Prelude.Maybe KafkaClusterDescription)
connectorSummary_kafkaCluster :: Lens' ConnectorSummary (Maybe KafkaClusterDescription)
connectorSummary_kafkaCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe KafkaClusterDescription
kafkaCluster :: Maybe KafkaClusterDescription
$sel:kafkaCluster:ConnectorSummary' :: ConnectorSummary -> Maybe KafkaClusterDescription
kafkaCluster} -> Maybe KafkaClusterDescription
kafkaCluster) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe KafkaClusterDescription
a -> ConnectorSummary
s {$sel:kafkaCluster:ConnectorSummary' :: Maybe KafkaClusterDescription
kafkaCluster = Maybe KafkaClusterDescription
a} :: ConnectorSummary)

-- | The type of client authentication used to connect to the Apache Kafka
-- cluster. The value is NONE when no client authentication is used.
connectorSummary_kafkaClusterClientAuthentication :: Lens.Lens' ConnectorSummary (Prelude.Maybe KafkaClusterClientAuthenticationDescription)
connectorSummary_kafkaClusterClientAuthentication :: Lens'
  ConnectorSummary
  (Maybe KafkaClusterClientAuthenticationDescription)
connectorSummary_kafkaClusterClientAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication :: Maybe KafkaClusterClientAuthenticationDescription
$sel:kafkaClusterClientAuthentication:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication} -> Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe KafkaClusterClientAuthenticationDescription
a -> ConnectorSummary
s {$sel:kafkaClusterClientAuthentication:ConnectorSummary' :: Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication = Maybe KafkaClusterClientAuthenticationDescription
a} :: ConnectorSummary)

-- | Details of encryption in transit to the Apache Kafka cluster.
connectorSummary_kafkaClusterEncryptionInTransit :: Lens.Lens' ConnectorSummary (Prelude.Maybe KafkaClusterEncryptionInTransitDescription)
connectorSummary_kafkaClusterEncryptionInTransit :: Lens'
  ConnectorSummary (Maybe KafkaClusterEncryptionInTransitDescription)
connectorSummary_kafkaClusterEncryptionInTransit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit :: Maybe KafkaClusterEncryptionInTransitDescription
$sel:kafkaClusterEncryptionInTransit:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit} -> Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe KafkaClusterEncryptionInTransitDescription
a -> ConnectorSummary
s {$sel:kafkaClusterEncryptionInTransit:ConnectorSummary' :: Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit = Maybe KafkaClusterEncryptionInTransitDescription
a} :: ConnectorSummary)

-- | The version of Kafka Connect. It has to be compatible with both the
-- Apache Kafka cluster\'s version and the plugins.
connectorSummary_kafkaConnectVersion :: Lens.Lens' ConnectorSummary (Prelude.Maybe Prelude.Text)
connectorSummary_kafkaConnectVersion :: Lens' ConnectorSummary (Maybe Text)
connectorSummary_kafkaConnectVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe Text
kafkaConnectVersion :: Maybe Text
$sel:kafkaConnectVersion:ConnectorSummary' :: ConnectorSummary -> Maybe Text
kafkaConnectVersion} -> Maybe Text
kafkaConnectVersion) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe Text
a -> ConnectorSummary
s {$sel:kafkaConnectVersion:ConnectorSummary' :: Maybe Text
kafkaConnectVersion = Maybe Text
a} :: ConnectorSummary)

-- | The settings for delivering connector logs to Amazon CloudWatch Logs.
connectorSummary_logDelivery :: Lens.Lens' ConnectorSummary (Prelude.Maybe LogDeliveryDescription)
connectorSummary_logDelivery :: Lens' ConnectorSummary (Maybe LogDeliveryDescription)
connectorSummary_logDelivery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe LogDeliveryDescription
logDelivery :: Maybe LogDeliveryDescription
$sel:logDelivery:ConnectorSummary' :: ConnectorSummary -> Maybe LogDeliveryDescription
logDelivery} -> Maybe LogDeliveryDescription
logDelivery) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe LogDeliveryDescription
a -> ConnectorSummary
s {$sel:logDelivery:ConnectorSummary' :: Maybe LogDeliveryDescription
logDelivery = Maybe LogDeliveryDescription
a} :: ConnectorSummary)

-- | Specifies which plugins were used for this connector.
connectorSummary_plugins :: Lens.Lens' ConnectorSummary (Prelude.Maybe [PluginDescription])
connectorSummary_plugins :: Lens' ConnectorSummary (Maybe [PluginDescription])
connectorSummary_plugins = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe [PluginDescription]
plugins :: Maybe [PluginDescription]
$sel:plugins:ConnectorSummary' :: ConnectorSummary -> Maybe [PluginDescription]
plugins} -> Maybe [PluginDescription]
plugins) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe [PluginDescription]
a -> ConnectorSummary
s {$sel:plugins:ConnectorSummary' :: Maybe [PluginDescription]
plugins = Maybe [PluginDescription]
a} :: ConnectorSummary) 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 Amazon Resource Name (ARN) of the IAM role used by the connector to
-- access Amazon Web Services resources.
connectorSummary_serviceExecutionRoleArn :: Lens.Lens' ConnectorSummary (Prelude.Maybe Prelude.Text)
connectorSummary_serviceExecutionRoleArn :: Lens' ConnectorSummary (Maybe Text)
connectorSummary_serviceExecutionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe Text
serviceExecutionRoleArn :: Maybe Text
$sel:serviceExecutionRoleArn:ConnectorSummary' :: ConnectorSummary -> Maybe Text
serviceExecutionRoleArn} -> Maybe Text
serviceExecutionRoleArn) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe Text
a -> ConnectorSummary
s {$sel:serviceExecutionRoleArn:ConnectorSummary' :: Maybe Text
serviceExecutionRoleArn = Maybe Text
a} :: ConnectorSummary)

-- | The worker configurations that are in use with the connector.
connectorSummary_workerConfiguration :: Lens.Lens' ConnectorSummary (Prelude.Maybe WorkerConfigurationDescription)
connectorSummary_workerConfiguration :: Lens' ConnectorSummary (Maybe WorkerConfigurationDescription)
connectorSummary_workerConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorSummary' {Maybe WorkerConfigurationDescription
workerConfiguration :: Maybe WorkerConfigurationDescription
$sel:workerConfiguration:ConnectorSummary' :: ConnectorSummary -> Maybe WorkerConfigurationDescription
workerConfiguration} -> Maybe WorkerConfigurationDescription
workerConfiguration) (\s :: ConnectorSummary
s@ConnectorSummary' {} Maybe WorkerConfigurationDescription
a -> ConnectorSummary
s {$sel:workerConfiguration:ConnectorSummary' :: Maybe WorkerConfigurationDescription
workerConfiguration = Maybe WorkerConfigurationDescription
a} :: ConnectorSummary)

instance Data.FromJSON ConnectorSummary where
  parseJSON :: Value -> Parser ConnectorSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ConnectorSummary"
      ( \Object
x ->
          Maybe CapacityDescription
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorState
-> Maybe ISO8601
-> Maybe Text
-> Maybe KafkaClusterDescription
-> Maybe KafkaClusterClientAuthenticationDescription
-> Maybe KafkaClusterEncryptionInTransitDescription
-> Maybe Text
-> Maybe LogDeliveryDescription
-> Maybe [PluginDescription]
-> Maybe Text
-> Maybe WorkerConfigurationDescription
-> ConnectorSummary
ConnectorSummary'
            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
"capacity")
            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
"connectorArn")
            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
"connectorDescription")
            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
"connectorName")
            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
"connectorState")
            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
"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
"kafkaCluster")
            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
"kafkaClusterClientAuthentication")
            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
"kafkaClusterEncryptionInTransit")
            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
"kafkaConnectVersion")
            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
"logDelivery")
            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
"plugins" 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
"serviceExecutionRoleArn")
            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
"workerConfiguration")
      )

instance Prelude.Hashable ConnectorSummary where
  hashWithSalt :: Int -> ConnectorSummary -> Int
hashWithSalt Int
_salt ConnectorSummary' {Maybe [PluginDescription]
Maybe Text
Maybe ISO8601
Maybe ConnectorState
Maybe KafkaClusterClientAuthenticationDescription
Maybe KafkaClusterEncryptionInTransitDescription
Maybe CapacityDescription
Maybe KafkaClusterDescription
Maybe WorkerConfigurationDescription
Maybe LogDeliveryDescription
workerConfiguration :: Maybe WorkerConfigurationDescription
serviceExecutionRoleArn :: Maybe Text
plugins :: Maybe [PluginDescription]
logDelivery :: Maybe LogDeliveryDescription
kafkaConnectVersion :: Maybe Text
kafkaClusterEncryptionInTransit :: Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterClientAuthentication :: Maybe KafkaClusterClientAuthenticationDescription
kafkaCluster :: Maybe KafkaClusterDescription
currentVersion :: Maybe Text
creationTime :: Maybe ISO8601
connectorState :: Maybe ConnectorState
connectorName :: Maybe Text
connectorDescription :: Maybe Text
connectorArn :: Maybe Text
capacity :: Maybe CapacityDescription
$sel:workerConfiguration:ConnectorSummary' :: ConnectorSummary -> Maybe WorkerConfigurationDescription
$sel:serviceExecutionRoleArn:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:plugins:ConnectorSummary' :: ConnectorSummary -> Maybe [PluginDescription]
$sel:logDelivery:ConnectorSummary' :: ConnectorSummary -> Maybe LogDeliveryDescription
$sel:kafkaConnectVersion:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:kafkaClusterEncryptionInTransit:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterEncryptionInTransitDescription
$sel:kafkaClusterClientAuthentication:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterClientAuthenticationDescription
$sel:kafkaCluster:ConnectorSummary' :: ConnectorSummary -> Maybe KafkaClusterDescription
$sel:currentVersion:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:creationTime:ConnectorSummary' :: ConnectorSummary -> Maybe ISO8601
$sel:connectorState:ConnectorSummary' :: ConnectorSummary -> Maybe ConnectorState
$sel:connectorName:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:connectorDescription:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:connectorArn:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:capacity:ConnectorSummary' :: ConnectorSummary -> Maybe CapacityDescription
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CapacityDescription
capacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorState
connectorState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KafkaClusterDescription
kafkaCluster
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kafkaConnectVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogDeliveryDescription
logDelivery
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PluginDescription]
plugins
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceExecutionRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkerConfigurationDescription
workerConfiguration

instance Prelude.NFData ConnectorSummary where
  rnf :: ConnectorSummary -> ()
rnf ConnectorSummary' {Maybe [PluginDescription]
Maybe Text
Maybe ISO8601
Maybe ConnectorState
Maybe KafkaClusterClientAuthenticationDescription
Maybe KafkaClusterEncryptionInTransitDescription
Maybe CapacityDescription
Maybe KafkaClusterDescription
Maybe WorkerConfigurationDescription
Maybe LogDeliveryDescription
workerConfiguration :: Maybe WorkerConfigurationDescription
serviceExecutionRoleArn :: Maybe Text
plugins :: Maybe [PluginDescription]
logDelivery :: Maybe LogDeliveryDescription
kafkaConnectVersion :: Maybe Text
kafkaClusterEncryptionInTransit :: Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterClientAuthentication :: Maybe KafkaClusterClientAuthenticationDescription
kafkaCluster :: Maybe KafkaClusterDescription
currentVersion :: Maybe Text
creationTime :: Maybe ISO8601
connectorState :: Maybe ConnectorState
connectorName :: Maybe Text
connectorDescription :: Maybe Text
connectorArn :: Maybe Text
capacity :: Maybe CapacityDescription
$sel:workerConfiguration:ConnectorSummary' :: ConnectorSummary -> Maybe WorkerConfigurationDescription
$sel:serviceExecutionRoleArn:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:plugins:ConnectorSummary' :: ConnectorSummary -> Maybe [PluginDescription]
$sel:logDelivery:ConnectorSummary' :: ConnectorSummary -> Maybe LogDeliveryDescription
$sel:kafkaConnectVersion:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:kafkaClusterEncryptionInTransit:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterEncryptionInTransitDescription
$sel:kafkaClusterClientAuthentication:ConnectorSummary' :: ConnectorSummary
-> Maybe KafkaClusterClientAuthenticationDescription
$sel:kafkaCluster:ConnectorSummary' :: ConnectorSummary -> Maybe KafkaClusterDescription
$sel:currentVersion:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:creationTime:ConnectorSummary' :: ConnectorSummary -> Maybe ISO8601
$sel:connectorState:ConnectorSummary' :: ConnectorSummary -> Maybe ConnectorState
$sel:connectorName:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:connectorDescription:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:connectorArn:ConnectorSummary' :: ConnectorSummary -> Maybe Text
$sel:capacity:ConnectorSummary' :: ConnectorSummary -> Maybe CapacityDescription
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CapacityDescription
capacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorState
connectorState
      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 Text
currentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KafkaClusterDescription
kafkaCluster
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KafkaClusterClientAuthenticationDescription
kafkaClusterClientAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KafkaClusterEncryptionInTransitDescription
kafkaClusterEncryptionInTransit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kafkaConnectVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogDeliveryDescription
logDelivery
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PluginDescription]
plugins
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceExecutionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkerConfigurationDescription
workerConfiguration