module Stratosphere.KafkaConnect.Connector (
module Exports, Connector(..), mkConnector
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.CapacityProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.KafkaClusterProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.KafkaClusterClientAuthenticationProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.KafkaClusterEncryptionInTransitProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.LogDeliveryProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.PluginProperty as Exports
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.WorkerConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Connector
=
Connector {Connector -> ()
haddock_workaround_ :: (),
Connector -> CapacityProperty
capacity :: CapacityProperty,
Connector -> Map Text (Value Text)
connectorConfiguration :: (Prelude.Map Prelude.Text (Value Prelude.Text)),
Connector -> Maybe (Value Text)
connectorDescription :: (Prelude.Maybe (Value Prelude.Text)),
Connector -> Value Text
connectorName :: (Value Prelude.Text),
Connector -> KafkaClusterProperty
kafkaCluster :: KafkaClusterProperty,
Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty,
Connector -> KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty,
Connector -> Value Text
kafkaConnectVersion :: (Value Prelude.Text),
Connector -> Maybe LogDeliveryProperty
logDelivery :: (Prelude.Maybe LogDeliveryProperty),
Connector -> [PluginProperty]
plugins :: [PluginProperty],
Connector -> Value Text
serviceExecutionRoleArn :: (Value Prelude.Text),
Connector -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
Connector -> Maybe WorkerConfigurationProperty
workerConfiguration :: (Prelude.Maybe WorkerConfigurationProperty)}
deriving stock (Connector -> Connector -> Bool
(Connector -> Connector -> Bool)
-> (Connector -> Connector -> Bool) -> Eq Connector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Connector -> Connector -> Bool
== :: Connector -> Connector -> Bool
$c/= :: Connector -> Connector -> Bool
/= :: Connector -> Connector -> Bool
Prelude.Eq, Int -> Connector -> ShowS
[Connector] -> ShowS
Connector -> String
(Int -> Connector -> ShowS)
-> (Connector -> String)
-> ([Connector] -> ShowS)
-> Show Connector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Connector -> ShowS
showsPrec :: Int -> Connector -> ShowS
$cshow :: Connector -> String
show :: Connector -> String
$cshowList :: [Connector] -> ShowS
showList :: [Connector] -> ShowS
Prelude.Show)
mkConnector ::
CapacityProperty
-> Prelude.Map Prelude.Text (Value Prelude.Text)
-> Value Prelude.Text
-> KafkaClusterProperty
-> KafkaClusterClientAuthenticationProperty
-> KafkaClusterEncryptionInTransitProperty
-> Value Prelude.Text
-> [PluginProperty] -> Value Prelude.Text -> Connector
mkConnector :: CapacityProperty
-> Map Text (Value Text)
-> Value Text
-> KafkaClusterProperty
-> KafkaClusterClientAuthenticationProperty
-> KafkaClusterEncryptionInTransitProperty
-> Value Text
-> [PluginProperty]
-> Value Text
-> Connector
mkConnector
CapacityProperty
capacity
Map Text (Value Text)
connectorConfiguration
Value Text
connectorName
KafkaClusterProperty
kafkaCluster
KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication
KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit
Value Text
kafkaConnectVersion
[PluginProperty]
plugins
Value Text
serviceExecutionRoleArn
= Connector
{haddock_workaround_ :: ()
haddock_workaround_ = (), capacity :: CapacityProperty
capacity = CapacityProperty
capacity,
connectorConfiguration :: Map Text (Value Text)
connectorConfiguration = Map Text (Value Text)
connectorConfiguration,
connectorName :: Value Text
connectorName = Value Text
connectorName, kafkaCluster :: KafkaClusterProperty
kafkaCluster = KafkaClusterProperty
kafkaCluster,
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication = KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication,
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit = KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit,
kafkaConnectVersion :: Value Text
kafkaConnectVersion = Value Text
kafkaConnectVersion, plugins :: [PluginProperty]
plugins = [PluginProperty]
plugins,
serviceExecutionRoleArn :: Value Text
serviceExecutionRoleArn = Value Text
serviceExecutionRoleArn,
connectorDescription :: Maybe (Value Text)
connectorDescription = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
logDelivery :: Maybe LogDeliveryProperty
logDelivery = Maybe LogDeliveryProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing,
workerConfiguration :: Maybe WorkerConfigurationProperty
workerConfiguration = Maybe WorkerConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Connector where
toResourceProperties :: Connector -> ResourceProperties
toResourceProperties Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::KafkaConnect::Connector",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Capacity" Key -> CapacityProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CapacityProperty
capacity,
Key
"ConnectorConfiguration" Key -> Map Text (Value Text) -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Map Text (Value Text)
connectorConfiguration,
Key
"ConnectorName" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
connectorName,
Key
"KafkaCluster" Key -> KafkaClusterProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterProperty
kafkaCluster,
Key
"KafkaClusterClientAuthentication"
Key -> KafkaClusterClientAuthenticationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication,
Key
"KafkaClusterEncryptionInTransit"
Key -> KafkaClusterEncryptionInTransitProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit,
Key
"KafkaConnectVersion" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
kafkaConnectVersion,
Key
"Plugins" Key -> [PluginProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [PluginProperty]
plugins,
Key
"ServiceExecutionRoleArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
serviceExecutionRoleArn]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConnectorDescription" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
connectorDescription,
Key -> LogDeliveryProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LogDelivery" (LogDeliveryProperty -> (Key, Value))
-> Maybe LogDeliveryProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LogDeliveryProperty
logDelivery,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
Key -> WorkerConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WorkerConfiguration" (WorkerConfigurationProperty -> (Key, Value))
-> Maybe WorkerConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WorkerConfigurationProperty
workerConfiguration]))}
instance JSON.ToJSON Connector where
toJSON :: Connector -> Value
toJSON Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Capacity" Key -> CapacityProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CapacityProperty
capacity,
Key
"ConnectorConfiguration" Key -> Map Text (Value Text) -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Map Text (Value Text)
connectorConfiguration,
Key
"ConnectorName" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
connectorName,
Key
"KafkaCluster" Key -> KafkaClusterProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterProperty
kafkaCluster,
Key
"KafkaClusterClientAuthentication"
Key -> KafkaClusterClientAuthenticationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication,
Key
"KafkaClusterEncryptionInTransit"
Key -> KafkaClusterEncryptionInTransitProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit,
Key
"KafkaConnectVersion" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
kafkaConnectVersion,
Key
"Plugins" Key -> [PluginProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [PluginProperty]
plugins,
Key
"ServiceExecutionRoleArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
serviceExecutionRoleArn]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConnectorDescription" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
connectorDescription,
Key -> LogDeliveryProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LogDelivery" (LogDeliveryProperty -> (Key, Value))
-> Maybe LogDeliveryProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LogDeliveryProperty
logDelivery,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
Key -> WorkerConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WorkerConfiguration" (WorkerConfigurationProperty -> (Key, Value))
-> Maybe WorkerConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WorkerConfigurationProperty
workerConfiguration])))
instance Property "Capacity" Connector where
type PropertyType "Capacity" Connector = CapacityProperty
set :: PropertyType "Capacity" Connector -> Connector -> Connector
set PropertyType "Capacity" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..} = Connector {capacity :: CapacityProperty
capacity = PropertyType "Capacity" Connector
CapacityProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
KafkaClusterProperty
haddock_workaround_ :: ()
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "ConnectorConfiguration" Connector where
type PropertyType "ConnectorConfiguration" Connector = Prelude.Map Prelude.Text (Value Prelude.Text)
set :: PropertyType "ConnectorConfiguration" Connector
-> Connector -> Connector
set PropertyType "ConnectorConfiguration" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {connectorConfiguration :: Map Text (Value Text)
connectorConfiguration = Map Text (Value Text)
PropertyType "ConnectorConfiguration" Connector
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "ConnectorDescription" Connector where
type PropertyType "ConnectorDescription" Connector = Value Prelude.Text
set :: PropertyType "ConnectorDescription" Connector
-> Connector -> Connector
set PropertyType "ConnectorDescription" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {connectorDescription :: Maybe (Value Text)
connectorDescription = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ConnectorDescription" Connector
Value Text
newValue, [PluginProperty]
Maybe [Tag]
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "ConnectorName" Connector where
type PropertyType "ConnectorName" Connector = Value Prelude.Text
set :: PropertyType "ConnectorName" Connector -> Connector -> Connector
set PropertyType "ConnectorName" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {connectorName :: Value Text
connectorName = PropertyType "ConnectorName" Connector
Value Text
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "KafkaCluster" Connector where
type PropertyType "KafkaCluster" Connector = KafkaClusterProperty
set :: PropertyType "KafkaCluster" Connector -> Connector -> Connector
set PropertyType "KafkaCluster" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {kafkaCluster :: KafkaClusterProperty
kafkaCluster = PropertyType "KafkaCluster" Connector
KafkaClusterProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "KafkaClusterClientAuthentication" Connector where
type PropertyType "KafkaClusterClientAuthentication" Connector = KafkaClusterClientAuthenticationProperty
set :: PropertyType "KafkaClusterClientAuthentication" Connector
-> Connector -> Connector
set PropertyType "KafkaClusterClientAuthentication" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterClientAuthentication = PropertyType "KafkaClusterClientAuthentication" Connector
KafkaClusterClientAuthenticationProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "KafkaClusterEncryptionInTransit" Connector where
type PropertyType "KafkaClusterEncryptionInTransit" Connector = KafkaClusterEncryptionInTransitProperty
set :: PropertyType "KafkaClusterEncryptionInTransit" Connector
-> Connector -> Connector
set PropertyType "KafkaClusterEncryptionInTransit" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaClusterEncryptionInTransit = PropertyType "KafkaClusterEncryptionInTransit" Connector
KafkaClusterEncryptionInTransitProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "KafkaConnectVersion" Connector where
type PropertyType "KafkaConnectVersion" Connector = Value Prelude.Text
set :: PropertyType "KafkaConnectVersion" Connector
-> Connector -> Connector
set PropertyType "KafkaConnectVersion" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {kafkaConnectVersion :: Value Text
kafkaConnectVersion = PropertyType "KafkaConnectVersion" Connector
Value Text
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "LogDelivery" Connector where
type PropertyType "LogDelivery" Connector = LogDeliveryProperty
set :: PropertyType "LogDelivery" Connector -> Connector -> Connector
set PropertyType "LogDelivery" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {logDelivery :: Maybe LogDeliveryProperty
logDelivery = LogDeliveryProperty -> Maybe LogDeliveryProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LogDelivery" Connector
LogDeliveryProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "Plugins" Connector where
type PropertyType "Plugins" Connector = [PluginProperty]
set :: PropertyType "Plugins" Connector -> Connector -> Connector
set PropertyType "Plugins" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..} = Connector {plugins :: [PluginProperty]
plugins = [PluginProperty]
PropertyType "Plugins" Connector
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "ServiceExecutionRoleArn" Connector where
type PropertyType "ServiceExecutionRoleArn" Connector = Value Prelude.Text
set :: PropertyType "ServiceExecutionRoleArn" Connector
-> Connector -> Connector
set PropertyType "ServiceExecutionRoleArn" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {serviceExecutionRoleArn :: Value Text
serviceExecutionRoleArn = PropertyType "ServiceExecutionRoleArn" Connector
Value Text
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "Tags" Connector where
type PropertyType "Tags" Connector = [Tag]
set :: PropertyType "Tags" Connector -> Connector -> Connector
set PropertyType "Tags" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" Connector
newValue, [PluginProperty]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
workerConfiguration :: Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
instance Property "WorkerConfiguration" Connector where
type PropertyType "WorkerConfiguration" Connector = WorkerConfigurationProperty
set :: PropertyType "WorkerConfiguration" Connector
-> Connector -> Connector
set PropertyType "WorkerConfiguration" Connector
newValue Connector {[PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe WorkerConfigurationProperty
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: Connector -> ()
capacity :: Connector -> CapacityProperty
connectorConfiguration :: Connector -> Map Text (Value Text)
connectorDescription :: Connector -> Maybe (Value Text)
connectorName :: Connector -> Value Text
kafkaCluster :: Connector -> KafkaClusterProperty
kafkaClusterClientAuthentication :: Connector -> KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: Connector -> KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Connector -> Value Text
logDelivery :: Connector -> Maybe LogDeliveryProperty
plugins :: Connector -> [PluginProperty]
serviceExecutionRoleArn :: Connector -> Value Text
tags :: Connector -> Maybe [Tag]
workerConfiguration :: Connector -> Maybe WorkerConfigurationProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
workerConfiguration :: Maybe WorkerConfigurationProperty
..}
= Connector {workerConfiguration :: Maybe WorkerConfigurationProperty
workerConfiguration = WorkerConfigurationProperty -> Maybe WorkerConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WorkerConfiguration" Connector
WorkerConfigurationProperty
newValue, [PluginProperty]
Maybe [Tag]
Maybe (Value Text)
Maybe LogDeliveryProperty
()
Map Text (Value Text)
Value Text
KafkaClusterClientAuthenticationProperty
KafkaClusterEncryptionInTransitProperty
CapacityProperty
KafkaClusterProperty
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
capacity :: CapacityProperty
connectorConfiguration :: Map Text (Value Text)
connectorDescription :: Maybe (Value Text)
connectorName :: Value Text
kafkaCluster :: KafkaClusterProperty
kafkaClusterClientAuthentication :: KafkaClusterClientAuthenticationProperty
kafkaClusterEncryptionInTransit :: KafkaClusterEncryptionInTransitProperty
kafkaConnectVersion :: Value Text
logDelivery :: Maybe LogDeliveryProperty
plugins :: [PluginProperty]
serviceExecutionRoleArn :: Value Text
tags :: Maybe [Tag]
..}