{-# 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.AppFlow.Types.ConnectorConfiguration
-- 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.AppFlow.Types.ConnectorConfiguration where

import Amazonka.AppFlow.Types.AuthenticationConfig
import Amazonka.AppFlow.Types.ConnectorMetadata
import Amazonka.AppFlow.Types.ConnectorProvisioningConfig
import Amazonka.AppFlow.Types.ConnectorProvisioningType
import Amazonka.AppFlow.Types.ConnectorRuntimeSetting
import Amazonka.AppFlow.Types.ConnectorType
import Amazonka.AppFlow.Types.Operators
import Amazonka.AppFlow.Types.ScheduleFrequencyType
import Amazonka.AppFlow.Types.TriggerType
import Amazonka.AppFlow.Types.WriteOperationType
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The configuration settings related to a given connector.
--
-- /See:/ 'newConnectorConfiguration' smart constructor.
data ConnectorConfiguration = ConnectorConfiguration'
  { -- | The authentication config required for the connector.
    ConnectorConfiguration -> Maybe AuthenticationConfig
authenticationConfig :: Prelude.Maybe AuthenticationConfig,
    -- | Specifies whether the connector can be used as a destination.
    ConnectorConfiguration -> Maybe Bool
canUseAsDestination :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether the connector can be used as a source.
    ConnectorConfiguration -> Maybe Bool
canUseAsSource :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) for the registered connector.
    ConnectorConfiguration -> Maybe Text
connectorArn :: Prelude.Maybe Prelude.Text,
    -- | A description about the connector.
    ConnectorConfiguration -> Maybe Text
connectorDescription :: Prelude.Maybe Prelude.Text,
    -- | The label used for registering the connector.
    ConnectorConfiguration -> Maybe Text
connectorLabel :: Prelude.Maybe Prelude.Text,
    -- | Specifies connector-specific metadata such as @oAuthScopes@,
    -- @supportedRegions@, @privateLinkServiceUrl@, and so on.
    ConnectorConfiguration -> Maybe ConnectorMetadata
connectorMetadata :: Prelude.Maybe ConnectorMetadata,
    -- | The connection modes that the connector supports.
    ConnectorConfiguration -> Maybe [Text]
connectorModes :: Prelude.Maybe [Prelude.Text],
    -- | The connector name.
    ConnectorConfiguration -> Maybe Text
connectorName :: Prelude.Maybe Prelude.Text,
    -- | The owner who developed the connector.
    ConnectorConfiguration -> Maybe Text
connectorOwner :: Prelude.Maybe Prelude.Text,
    -- | The configuration required for registering the connector.
    ConnectorConfiguration -> Maybe ConnectorProvisioningConfig
connectorProvisioningConfig :: Prelude.Maybe ConnectorProvisioningConfig,
    -- | The provisioning type used to register the connector.
    ConnectorConfiguration -> Maybe ConnectorProvisioningType
connectorProvisioningType :: Prelude.Maybe ConnectorProvisioningType,
    -- | The required connector runtime settings.
    ConnectorConfiguration -> Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings :: Prelude.Maybe [ConnectorRuntimeSetting],
    -- | The connector type.
    ConnectorConfiguration -> Maybe ConnectorType
connectorType :: Prelude.Maybe ConnectorType,
    -- | The connector version.
    ConnectorConfiguration -> Maybe Text
connectorVersion :: Prelude.Maybe Prelude.Text,
    -- | Specifies if PrivateLink is enabled for that connector.
    ConnectorConfiguration -> Maybe Bool
isPrivateLinkEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Specifies if a PrivateLink endpoint URL is required.
    ConnectorConfiguration -> Maybe Bool
isPrivateLinkEndpointUrlRequired :: Prelude.Maybe Prelude.Bool,
    -- | Logo URL of the connector.
    ConnectorConfiguration -> Maybe Text
logoURL :: Prelude.Maybe Prelude.Text,
    -- | The date on which the connector was registered.
    ConnectorConfiguration -> Maybe POSIX
registeredAt :: Prelude.Maybe Data.POSIX,
    -- | Information about who registered the connector.
    ConnectorConfiguration -> Maybe Text
registeredBy :: Prelude.Maybe Prelude.Text,
    -- | A list of API versions that are supported by the connector.
    ConnectorConfiguration -> Maybe [Text]
supportedApiVersions :: Prelude.Maybe [Prelude.Text],
    -- | Lists the connectors that are available for use as destinations.
    ConnectorConfiguration -> Maybe [ConnectorType]
supportedDestinationConnectors :: Prelude.Maybe [ConnectorType],
    -- | A list of operators supported by the connector.
    ConnectorConfiguration -> Maybe [Operators]
supportedOperators :: Prelude.Maybe [Operators],
    -- | Specifies the supported flow frequency for that connector.
    ConnectorConfiguration -> Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies :: Prelude.Maybe [ScheduleFrequencyType],
    -- | Specifies the supported trigger types for the flow.
    ConnectorConfiguration -> Maybe [TriggerType]
supportedTriggerTypes :: Prelude.Maybe [TriggerType],
    -- | A list of write operations supported by the connector.
    ConnectorConfiguration -> Maybe [WriteOperationType]
supportedWriteOperations :: Prelude.Maybe [WriteOperationType]
  }
  deriving (ConnectorConfiguration -> ConnectorConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectorConfiguration -> ConnectorConfiguration -> Bool
$c/= :: ConnectorConfiguration -> ConnectorConfiguration -> Bool
== :: ConnectorConfiguration -> ConnectorConfiguration -> Bool
$c== :: ConnectorConfiguration -> ConnectorConfiguration -> Bool
Prelude.Eq, ReadPrec [ConnectorConfiguration]
ReadPrec ConnectorConfiguration
Int -> ReadS ConnectorConfiguration
ReadS [ConnectorConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConnectorConfiguration]
$creadListPrec :: ReadPrec [ConnectorConfiguration]
readPrec :: ReadPrec ConnectorConfiguration
$creadPrec :: ReadPrec ConnectorConfiguration
readList :: ReadS [ConnectorConfiguration]
$creadList :: ReadS [ConnectorConfiguration]
readsPrec :: Int -> ReadS ConnectorConfiguration
$creadsPrec :: Int -> ReadS ConnectorConfiguration
Prelude.Read, Int -> ConnectorConfiguration -> ShowS
[ConnectorConfiguration] -> ShowS
ConnectorConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectorConfiguration] -> ShowS
$cshowList :: [ConnectorConfiguration] -> ShowS
show :: ConnectorConfiguration -> String
$cshow :: ConnectorConfiguration -> String
showsPrec :: Int -> ConnectorConfiguration -> ShowS
$cshowsPrec :: Int -> ConnectorConfiguration -> ShowS
Prelude.Show, forall x. Rep ConnectorConfiguration x -> ConnectorConfiguration
forall x. ConnectorConfiguration -> Rep ConnectorConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectorConfiguration x -> ConnectorConfiguration
$cfrom :: forall x. ConnectorConfiguration -> Rep ConnectorConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'ConnectorConfiguration' 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:
--
-- 'authenticationConfig', 'connectorConfiguration_authenticationConfig' - The authentication config required for the connector.
--
-- 'canUseAsDestination', 'connectorConfiguration_canUseAsDestination' - Specifies whether the connector can be used as a destination.
--
-- 'canUseAsSource', 'connectorConfiguration_canUseAsSource' - Specifies whether the connector can be used as a source.
--
-- 'connectorArn', 'connectorConfiguration_connectorArn' - The Amazon Resource Name (ARN) for the registered connector.
--
-- 'connectorDescription', 'connectorConfiguration_connectorDescription' - A description about the connector.
--
-- 'connectorLabel', 'connectorConfiguration_connectorLabel' - The label used for registering the connector.
--
-- 'connectorMetadata', 'connectorConfiguration_connectorMetadata' - Specifies connector-specific metadata such as @oAuthScopes@,
-- @supportedRegions@, @privateLinkServiceUrl@, and so on.
--
-- 'connectorModes', 'connectorConfiguration_connectorModes' - The connection modes that the connector supports.
--
-- 'connectorName', 'connectorConfiguration_connectorName' - The connector name.
--
-- 'connectorOwner', 'connectorConfiguration_connectorOwner' - The owner who developed the connector.
--
-- 'connectorProvisioningConfig', 'connectorConfiguration_connectorProvisioningConfig' - The configuration required for registering the connector.
--
-- 'connectorProvisioningType', 'connectorConfiguration_connectorProvisioningType' - The provisioning type used to register the connector.
--
-- 'connectorRuntimeSettings', 'connectorConfiguration_connectorRuntimeSettings' - The required connector runtime settings.
--
-- 'connectorType', 'connectorConfiguration_connectorType' - The connector type.
--
-- 'connectorVersion', 'connectorConfiguration_connectorVersion' - The connector version.
--
-- 'isPrivateLinkEnabled', 'connectorConfiguration_isPrivateLinkEnabled' - Specifies if PrivateLink is enabled for that connector.
--
-- 'isPrivateLinkEndpointUrlRequired', 'connectorConfiguration_isPrivateLinkEndpointUrlRequired' - Specifies if a PrivateLink endpoint URL is required.
--
-- 'logoURL', 'connectorConfiguration_logoURL' - Logo URL of the connector.
--
-- 'registeredAt', 'connectorConfiguration_registeredAt' - The date on which the connector was registered.
--
-- 'registeredBy', 'connectorConfiguration_registeredBy' - Information about who registered the connector.
--
-- 'supportedApiVersions', 'connectorConfiguration_supportedApiVersions' - A list of API versions that are supported by the connector.
--
-- 'supportedDestinationConnectors', 'connectorConfiguration_supportedDestinationConnectors' - Lists the connectors that are available for use as destinations.
--
-- 'supportedOperators', 'connectorConfiguration_supportedOperators' - A list of operators supported by the connector.
--
-- 'supportedSchedulingFrequencies', 'connectorConfiguration_supportedSchedulingFrequencies' - Specifies the supported flow frequency for that connector.
--
-- 'supportedTriggerTypes', 'connectorConfiguration_supportedTriggerTypes' - Specifies the supported trigger types for the flow.
--
-- 'supportedWriteOperations', 'connectorConfiguration_supportedWriteOperations' - A list of write operations supported by the connector.
newConnectorConfiguration ::
  ConnectorConfiguration
newConnectorConfiguration :: ConnectorConfiguration
newConnectorConfiguration =
  ConnectorConfiguration'
    { $sel:authenticationConfig:ConnectorConfiguration' :: Maybe AuthenticationConfig
authenticationConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:canUseAsDestination:ConnectorConfiguration' :: Maybe Bool
canUseAsDestination = forall a. Maybe a
Prelude.Nothing,
      $sel:canUseAsSource:ConnectorConfiguration' :: Maybe Bool
canUseAsSource = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorArn:ConnectorConfiguration' :: Maybe Text
connectorArn = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorDescription:ConnectorConfiguration' :: Maybe Text
connectorDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorLabel:ConnectorConfiguration' :: Maybe Text
connectorLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorMetadata:ConnectorConfiguration' :: Maybe ConnectorMetadata
connectorMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorModes:ConnectorConfiguration' :: Maybe [Text]
connectorModes = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorName:ConnectorConfiguration' :: Maybe Text
connectorName = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorOwner:ConnectorConfiguration' :: Maybe Text
connectorOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorProvisioningConfig:ConnectorConfiguration' :: Maybe ConnectorProvisioningConfig
connectorProvisioningConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorProvisioningType:ConnectorConfiguration' :: Maybe ConnectorProvisioningType
connectorProvisioningType = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorRuntimeSettings:ConnectorConfiguration' :: Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorType:ConnectorConfiguration' :: Maybe ConnectorType
connectorType = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorVersion:ConnectorConfiguration' :: Maybe Text
connectorVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:isPrivateLinkEnabled:ConnectorConfiguration' :: Maybe Bool
isPrivateLinkEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:isPrivateLinkEndpointUrlRequired:ConnectorConfiguration' :: Maybe Bool
isPrivateLinkEndpointUrlRequired = forall a. Maybe a
Prelude.Nothing,
      $sel:logoURL:ConnectorConfiguration' :: Maybe Text
logoURL = forall a. Maybe a
Prelude.Nothing,
      $sel:registeredAt:ConnectorConfiguration' :: Maybe POSIX
registeredAt = forall a. Maybe a
Prelude.Nothing,
      $sel:registeredBy:ConnectorConfiguration' :: Maybe Text
registeredBy = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedApiVersions:ConnectorConfiguration' :: Maybe [Text]
supportedApiVersions = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedDestinationConnectors:ConnectorConfiguration' :: Maybe [ConnectorType]
supportedDestinationConnectors = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedOperators:ConnectorConfiguration' :: Maybe [Operators]
supportedOperators = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedSchedulingFrequencies:ConnectorConfiguration' :: Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedTriggerTypes:ConnectorConfiguration' :: Maybe [TriggerType]
supportedTriggerTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedWriteOperations:ConnectorConfiguration' :: Maybe [WriteOperationType]
supportedWriteOperations = forall a. Maybe a
Prelude.Nothing
    }

-- | The authentication config required for the connector.
connectorConfiguration_authenticationConfig :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe AuthenticationConfig)
connectorConfiguration_authenticationConfig :: Lens' ConnectorConfiguration (Maybe AuthenticationConfig)
connectorConfiguration_authenticationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe AuthenticationConfig
authenticationConfig :: Maybe AuthenticationConfig
$sel:authenticationConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe AuthenticationConfig
authenticationConfig} -> Maybe AuthenticationConfig
authenticationConfig) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe AuthenticationConfig
a -> ConnectorConfiguration
s {$sel:authenticationConfig:ConnectorConfiguration' :: Maybe AuthenticationConfig
authenticationConfig = Maybe AuthenticationConfig
a} :: ConnectorConfiguration)

-- | Specifies whether the connector can be used as a destination.
connectorConfiguration_canUseAsDestination :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Bool)
connectorConfiguration_canUseAsDestination :: Lens' ConnectorConfiguration (Maybe Bool)
connectorConfiguration_canUseAsDestination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Bool
canUseAsDestination :: Maybe Bool
$sel:canUseAsDestination:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
canUseAsDestination} -> Maybe Bool
canUseAsDestination) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Bool
a -> ConnectorConfiguration
s {$sel:canUseAsDestination:ConnectorConfiguration' :: Maybe Bool
canUseAsDestination = Maybe Bool
a} :: ConnectorConfiguration)

-- | Specifies whether the connector can be used as a source.
connectorConfiguration_canUseAsSource :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Bool)
connectorConfiguration_canUseAsSource :: Lens' ConnectorConfiguration (Maybe Bool)
connectorConfiguration_canUseAsSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Bool
canUseAsSource :: Maybe Bool
$sel:canUseAsSource:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
canUseAsSource} -> Maybe Bool
canUseAsSource) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Bool
a -> ConnectorConfiguration
s {$sel:canUseAsSource:ConnectorConfiguration' :: Maybe Bool
canUseAsSource = Maybe Bool
a} :: ConnectorConfiguration)

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

-- | A description about the connector.
connectorConfiguration_connectorDescription :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_connectorDescription :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_connectorDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
connectorDescription :: Maybe Text
$sel:connectorDescription:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
connectorDescription} -> Maybe Text
connectorDescription) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:connectorDescription:ConnectorConfiguration' :: Maybe Text
connectorDescription = Maybe Text
a} :: ConnectorConfiguration)

-- | The label used for registering the connector.
connectorConfiguration_connectorLabel :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_connectorLabel :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_connectorLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
connectorLabel :: Maybe Text
$sel:connectorLabel:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
connectorLabel} -> Maybe Text
connectorLabel) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:connectorLabel:ConnectorConfiguration' :: Maybe Text
connectorLabel = Maybe Text
a} :: ConnectorConfiguration)

-- | Specifies connector-specific metadata such as @oAuthScopes@,
-- @supportedRegions@, @privateLinkServiceUrl@, and so on.
connectorConfiguration_connectorMetadata :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe ConnectorMetadata)
connectorConfiguration_connectorMetadata :: Lens' ConnectorConfiguration (Maybe ConnectorMetadata)
connectorConfiguration_connectorMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe ConnectorMetadata
connectorMetadata :: Maybe ConnectorMetadata
$sel:connectorMetadata:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorMetadata
connectorMetadata} -> Maybe ConnectorMetadata
connectorMetadata) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe ConnectorMetadata
a -> ConnectorConfiguration
s {$sel:connectorMetadata:ConnectorConfiguration' :: Maybe ConnectorMetadata
connectorMetadata = Maybe ConnectorMetadata
a} :: ConnectorConfiguration)

-- | The connection modes that the connector supports.
connectorConfiguration_connectorModes :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [Prelude.Text])
connectorConfiguration_connectorModes :: Lens' ConnectorConfiguration (Maybe [Text])
connectorConfiguration_connectorModes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [Text]
connectorModes :: Maybe [Text]
$sel:connectorModes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
connectorModes} -> Maybe [Text]
connectorModes) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [Text]
a -> ConnectorConfiguration
s {$sel:connectorModes:ConnectorConfiguration' :: Maybe [Text]
connectorModes = Maybe [Text]
a} :: ConnectorConfiguration) 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 connector name.
connectorConfiguration_connectorName :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_connectorName :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_connectorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
connectorName :: Maybe Text
$sel:connectorName:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
connectorName} -> Maybe Text
connectorName) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:connectorName:ConnectorConfiguration' :: Maybe Text
connectorName = Maybe Text
a} :: ConnectorConfiguration)

-- | The owner who developed the connector.
connectorConfiguration_connectorOwner :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_connectorOwner :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_connectorOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
connectorOwner :: Maybe Text
$sel:connectorOwner:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
connectorOwner} -> Maybe Text
connectorOwner) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:connectorOwner:ConnectorConfiguration' :: Maybe Text
connectorOwner = Maybe Text
a} :: ConnectorConfiguration)

-- | The configuration required for registering the connector.
connectorConfiguration_connectorProvisioningConfig :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe ConnectorProvisioningConfig)
connectorConfiguration_connectorProvisioningConfig :: Lens' ConnectorConfiguration (Maybe ConnectorProvisioningConfig)
connectorConfiguration_connectorProvisioningConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe ConnectorProvisioningConfig
connectorProvisioningConfig :: Maybe ConnectorProvisioningConfig
$sel:connectorProvisioningConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningConfig
connectorProvisioningConfig} -> Maybe ConnectorProvisioningConfig
connectorProvisioningConfig) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe ConnectorProvisioningConfig
a -> ConnectorConfiguration
s {$sel:connectorProvisioningConfig:ConnectorConfiguration' :: Maybe ConnectorProvisioningConfig
connectorProvisioningConfig = Maybe ConnectorProvisioningConfig
a} :: ConnectorConfiguration)

-- | The provisioning type used to register the connector.
connectorConfiguration_connectorProvisioningType :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe ConnectorProvisioningType)
connectorConfiguration_connectorProvisioningType :: Lens' ConnectorConfiguration (Maybe ConnectorProvisioningType)
connectorConfiguration_connectorProvisioningType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe ConnectorProvisioningType
connectorProvisioningType :: Maybe ConnectorProvisioningType
$sel:connectorProvisioningType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningType
connectorProvisioningType} -> Maybe ConnectorProvisioningType
connectorProvisioningType) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe ConnectorProvisioningType
a -> ConnectorConfiguration
s {$sel:connectorProvisioningType:ConnectorConfiguration' :: Maybe ConnectorProvisioningType
connectorProvisioningType = Maybe ConnectorProvisioningType
a} :: ConnectorConfiguration)

-- | The required connector runtime settings.
connectorConfiguration_connectorRuntimeSettings :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [ConnectorRuntimeSetting])
connectorConfiguration_connectorRuntimeSettings :: Lens' ConnectorConfiguration (Maybe [ConnectorRuntimeSetting])
connectorConfiguration_connectorRuntimeSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings :: Maybe [ConnectorRuntimeSetting]
$sel:connectorRuntimeSettings:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings} -> Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [ConnectorRuntimeSetting]
a -> ConnectorConfiguration
s {$sel:connectorRuntimeSettings:ConnectorConfiguration' :: Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings = Maybe [ConnectorRuntimeSetting]
a} :: ConnectorConfiguration) 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 connector type.
connectorConfiguration_connectorType :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe ConnectorType)
connectorConfiguration_connectorType :: Lens' ConnectorConfiguration (Maybe ConnectorType)
connectorConfiguration_connectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe ConnectorType
connectorType :: Maybe ConnectorType
$sel:connectorType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorType
connectorType} -> Maybe ConnectorType
connectorType) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe ConnectorType
a -> ConnectorConfiguration
s {$sel:connectorType:ConnectorConfiguration' :: Maybe ConnectorType
connectorType = Maybe ConnectorType
a} :: ConnectorConfiguration)

-- | The connector version.
connectorConfiguration_connectorVersion :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_connectorVersion :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_connectorVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
connectorVersion :: Maybe Text
$sel:connectorVersion:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
connectorVersion} -> Maybe Text
connectorVersion) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:connectorVersion:ConnectorConfiguration' :: Maybe Text
connectorVersion = Maybe Text
a} :: ConnectorConfiguration)

-- | Specifies if PrivateLink is enabled for that connector.
connectorConfiguration_isPrivateLinkEnabled :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Bool)
connectorConfiguration_isPrivateLinkEnabled :: Lens' ConnectorConfiguration (Maybe Bool)
connectorConfiguration_isPrivateLinkEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Bool
isPrivateLinkEnabled :: Maybe Bool
$sel:isPrivateLinkEnabled:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
isPrivateLinkEnabled} -> Maybe Bool
isPrivateLinkEnabled) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Bool
a -> ConnectorConfiguration
s {$sel:isPrivateLinkEnabled:ConnectorConfiguration' :: Maybe Bool
isPrivateLinkEnabled = Maybe Bool
a} :: ConnectorConfiguration)

-- | Specifies if a PrivateLink endpoint URL is required.
connectorConfiguration_isPrivateLinkEndpointUrlRequired :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Bool)
connectorConfiguration_isPrivateLinkEndpointUrlRequired :: Lens' ConnectorConfiguration (Maybe Bool)
connectorConfiguration_isPrivateLinkEndpointUrlRequired = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Bool
isPrivateLinkEndpointUrlRequired :: Maybe Bool
$sel:isPrivateLinkEndpointUrlRequired:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
isPrivateLinkEndpointUrlRequired} -> Maybe Bool
isPrivateLinkEndpointUrlRequired) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Bool
a -> ConnectorConfiguration
s {$sel:isPrivateLinkEndpointUrlRequired:ConnectorConfiguration' :: Maybe Bool
isPrivateLinkEndpointUrlRequired = Maybe Bool
a} :: ConnectorConfiguration)

-- | Logo URL of the connector.
connectorConfiguration_logoURL :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_logoURL :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_logoURL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
logoURL :: Maybe Text
$sel:logoURL:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
logoURL} -> Maybe Text
logoURL) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:logoURL:ConnectorConfiguration' :: Maybe Text
logoURL = Maybe Text
a} :: ConnectorConfiguration)

-- | The date on which the connector was registered.
connectorConfiguration_registeredAt :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.UTCTime)
connectorConfiguration_registeredAt :: Lens' ConnectorConfiguration (Maybe UTCTime)
connectorConfiguration_registeredAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe POSIX
registeredAt :: Maybe POSIX
$sel:registeredAt:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe POSIX
registeredAt} -> Maybe POSIX
registeredAt) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe POSIX
a -> ConnectorConfiguration
s {$sel:registeredAt:ConnectorConfiguration' :: Maybe POSIX
registeredAt = Maybe POSIX
a} :: ConnectorConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Information about who registered the connector.
connectorConfiguration_registeredBy :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe Prelude.Text)
connectorConfiguration_registeredBy :: Lens' ConnectorConfiguration (Maybe Text)
connectorConfiguration_registeredBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe Text
registeredBy :: Maybe Text
$sel:registeredBy:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
registeredBy} -> Maybe Text
registeredBy) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe Text
a -> ConnectorConfiguration
s {$sel:registeredBy:ConnectorConfiguration' :: Maybe Text
registeredBy = Maybe Text
a} :: ConnectorConfiguration)

-- | A list of API versions that are supported by the connector.
connectorConfiguration_supportedApiVersions :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [Prelude.Text])
connectorConfiguration_supportedApiVersions :: Lens' ConnectorConfiguration (Maybe [Text])
connectorConfiguration_supportedApiVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [Text]
supportedApiVersions :: Maybe [Text]
$sel:supportedApiVersions:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
supportedApiVersions} -> Maybe [Text]
supportedApiVersions) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [Text]
a -> ConnectorConfiguration
s {$sel:supportedApiVersions:ConnectorConfiguration' :: Maybe [Text]
supportedApiVersions = Maybe [Text]
a} :: ConnectorConfiguration) 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

-- | Lists the connectors that are available for use as destinations.
connectorConfiguration_supportedDestinationConnectors :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [ConnectorType])
connectorConfiguration_supportedDestinationConnectors :: Lens' ConnectorConfiguration (Maybe [ConnectorType])
connectorConfiguration_supportedDestinationConnectors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [ConnectorType]
supportedDestinationConnectors :: Maybe [ConnectorType]
$sel:supportedDestinationConnectors:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorType]
supportedDestinationConnectors} -> Maybe [ConnectorType]
supportedDestinationConnectors) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [ConnectorType]
a -> ConnectorConfiguration
s {$sel:supportedDestinationConnectors:ConnectorConfiguration' :: Maybe [ConnectorType]
supportedDestinationConnectors = Maybe [ConnectorType]
a} :: ConnectorConfiguration) 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

-- | A list of operators supported by the connector.
connectorConfiguration_supportedOperators :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [Operators])
connectorConfiguration_supportedOperators :: Lens' ConnectorConfiguration (Maybe [Operators])
connectorConfiguration_supportedOperators = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [Operators]
supportedOperators :: Maybe [Operators]
$sel:supportedOperators:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Operators]
supportedOperators} -> Maybe [Operators]
supportedOperators) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [Operators]
a -> ConnectorConfiguration
s {$sel:supportedOperators:ConnectorConfiguration' :: Maybe [Operators]
supportedOperators = Maybe [Operators]
a} :: ConnectorConfiguration) 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

-- | Specifies the supported flow frequency for that connector.
connectorConfiguration_supportedSchedulingFrequencies :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [ScheduleFrequencyType])
connectorConfiguration_supportedSchedulingFrequencies :: Lens' ConnectorConfiguration (Maybe [ScheduleFrequencyType])
connectorConfiguration_supportedSchedulingFrequencies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies :: Maybe [ScheduleFrequencyType]
$sel:supportedSchedulingFrequencies:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies} -> Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [ScheduleFrequencyType]
a -> ConnectorConfiguration
s {$sel:supportedSchedulingFrequencies:ConnectorConfiguration' :: Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies = Maybe [ScheduleFrequencyType]
a} :: ConnectorConfiguration) 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

-- | Specifies the supported trigger types for the flow.
connectorConfiguration_supportedTriggerTypes :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [TriggerType])
connectorConfiguration_supportedTriggerTypes :: Lens' ConnectorConfiguration (Maybe [TriggerType])
connectorConfiguration_supportedTriggerTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [TriggerType]
supportedTriggerTypes :: Maybe [TriggerType]
$sel:supportedTriggerTypes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [TriggerType]
supportedTriggerTypes} -> Maybe [TriggerType]
supportedTriggerTypes) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [TriggerType]
a -> ConnectorConfiguration
s {$sel:supportedTriggerTypes:ConnectorConfiguration' :: Maybe [TriggerType]
supportedTriggerTypes = Maybe [TriggerType]
a} :: ConnectorConfiguration) 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

-- | A list of write operations supported by the connector.
connectorConfiguration_supportedWriteOperations :: Lens.Lens' ConnectorConfiguration (Prelude.Maybe [WriteOperationType])
connectorConfiguration_supportedWriteOperations :: Lens' ConnectorConfiguration (Maybe [WriteOperationType])
connectorConfiguration_supportedWriteOperations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorConfiguration' {Maybe [WriteOperationType]
supportedWriteOperations :: Maybe [WriteOperationType]
$sel:supportedWriteOperations:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [WriteOperationType]
supportedWriteOperations} -> Maybe [WriteOperationType]
supportedWriteOperations) (\s :: ConnectorConfiguration
s@ConnectorConfiguration' {} Maybe [WriteOperationType]
a -> ConnectorConfiguration
s {$sel:supportedWriteOperations:ConnectorConfiguration' :: Maybe [WriteOperationType]
supportedWriteOperations = Maybe [WriteOperationType]
a} :: ConnectorConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromJSON ConnectorConfiguration where
  parseJSON :: Value -> Parser ConnectorConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ConnectorConfiguration"
      ( \Object
x ->
          Maybe AuthenticationConfig
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorMetadata
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorProvisioningConfig
-> Maybe ConnectorProvisioningType
-> Maybe [ConnectorRuntimeSetting]
-> Maybe ConnectorType
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe [Text]
-> Maybe [ConnectorType]
-> Maybe [Operators]
-> Maybe [ScheduleFrequencyType]
-> Maybe [TriggerType]
-> Maybe [WriteOperationType]
-> ConnectorConfiguration
ConnectorConfiguration'
            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
"authenticationConfig")
            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
"canUseAsDestination")
            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
"canUseAsSource")
            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
"connectorLabel")
            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
"connectorMetadata")
            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
"connectorModes" 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
"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
"connectorOwner")
            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
"connectorProvisioningConfig")
            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
"connectorProvisioningType")
            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
"connectorRuntimeSettings"
                            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
"connectorType")
            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
"connectorVersion")
            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
"isPrivateLinkEnabled")
            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
"isPrivateLinkEndpointUrlRequired")
            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
"logoURL")
            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
"registeredAt")
            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
"registeredBy")
            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
"supportedApiVersions"
                            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
"supportedDestinationConnectors"
                            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
"supportedOperators"
                            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
"supportedSchedulingFrequencies"
                            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
"supportedTriggerTypes"
                            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
"supportedWriteOperations"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ConnectorConfiguration where
  hashWithSalt :: Int -> ConnectorConfiguration -> Int
hashWithSalt Int
_salt ConnectorConfiguration' {Maybe Bool
Maybe [Text]
Maybe [ConnectorRuntimeSetting]
Maybe [ConnectorType]
Maybe [Operators]
Maybe [ScheduleFrequencyType]
Maybe [TriggerType]
Maybe [WriteOperationType]
Maybe Text
Maybe POSIX
Maybe ConnectorProvisioningType
Maybe ConnectorType
Maybe ConnectorProvisioningConfig
Maybe AuthenticationConfig
Maybe ConnectorMetadata
supportedWriteOperations :: Maybe [WriteOperationType]
supportedTriggerTypes :: Maybe [TriggerType]
supportedSchedulingFrequencies :: Maybe [ScheduleFrequencyType]
supportedOperators :: Maybe [Operators]
supportedDestinationConnectors :: Maybe [ConnectorType]
supportedApiVersions :: Maybe [Text]
registeredBy :: Maybe Text
registeredAt :: Maybe POSIX
logoURL :: Maybe Text
isPrivateLinkEndpointUrlRequired :: Maybe Bool
isPrivateLinkEnabled :: Maybe Bool
connectorVersion :: Maybe Text
connectorType :: Maybe ConnectorType
connectorRuntimeSettings :: Maybe [ConnectorRuntimeSetting]
connectorProvisioningType :: Maybe ConnectorProvisioningType
connectorProvisioningConfig :: Maybe ConnectorProvisioningConfig
connectorOwner :: Maybe Text
connectorName :: Maybe Text
connectorModes :: Maybe [Text]
connectorMetadata :: Maybe ConnectorMetadata
connectorLabel :: Maybe Text
connectorDescription :: Maybe Text
connectorArn :: Maybe Text
canUseAsSource :: Maybe Bool
canUseAsDestination :: Maybe Bool
authenticationConfig :: Maybe AuthenticationConfig
$sel:supportedWriteOperations:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [WriteOperationType]
$sel:supportedTriggerTypes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [TriggerType]
$sel:supportedSchedulingFrequencies:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ScheduleFrequencyType]
$sel:supportedOperators:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Operators]
$sel:supportedDestinationConnectors:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorType]
$sel:supportedApiVersions:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
$sel:registeredBy:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:registeredAt:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe POSIX
$sel:logoURL:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:isPrivateLinkEndpointUrlRequired:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:isPrivateLinkEnabled:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:connectorVersion:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorType
$sel:connectorRuntimeSettings:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorRuntimeSetting]
$sel:connectorProvisioningType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningType
$sel:connectorProvisioningConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningConfig
$sel:connectorOwner:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorName:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorModes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
$sel:connectorMetadata:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorMetadata
$sel:connectorLabel:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorDescription:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorArn:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:canUseAsSource:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:canUseAsDestination:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:authenticationConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe AuthenticationConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationConfig
authenticationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
canUseAsDestination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
canUseAsSource
      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
connectorLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorMetadata
connectorMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
connectorModes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorProvisioningConfig
connectorProvisioningConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorProvisioningType
connectorProvisioningType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorType
connectorType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isPrivateLinkEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isPrivateLinkEndpointUrlRequired
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logoURL
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
registeredAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
registeredBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
supportedApiVersions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ConnectorType]
supportedDestinationConnectors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Operators]
supportedOperators
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TriggerType]
supportedTriggerTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [WriteOperationType]
supportedWriteOperations

instance Prelude.NFData ConnectorConfiguration where
  rnf :: ConnectorConfiguration -> ()
rnf ConnectorConfiguration' {Maybe Bool
Maybe [Text]
Maybe [ConnectorRuntimeSetting]
Maybe [ConnectorType]
Maybe [Operators]
Maybe [ScheduleFrequencyType]
Maybe [TriggerType]
Maybe [WriteOperationType]
Maybe Text
Maybe POSIX
Maybe ConnectorProvisioningType
Maybe ConnectorType
Maybe ConnectorProvisioningConfig
Maybe AuthenticationConfig
Maybe ConnectorMetadata
supportedWriteOperations :: Maybe [WriteOperationType]
supportedTriggerTypes :: Maybe [TriggerType]
supportedSchedulingFrequencies :: Maybe [ScheduleFrequencyType]
supportedOperators :: Maybe [Operators]
supportedDestinationConnectors :: Maybe [ConnectorType]
supportedApiVersions :: Maybe [Text]
registeredBy :: Maybe Text
registeredAt :: Maybe POSIX
logoURL :: Maybe Text
isPrivateLinkEndpointUrlRequired :: Maybe Bool
isPrivateLinkEnabled :: Maybe Bool
connectorVersion :: Maybe Text
connectorType :: Maybe ConnectorType
connectorRuntimeSettings :: Maybe [ConnectorRuntimeSetting]
connectorProvisioningType :: Maybe ConnectorProvisioningType
connectorProvisioningConfig :: Maybe ConnectorProvisioningConfig
connectorOwner :: Maybe Text
connectorName :: Maybe Text
connectorModes :: Maybe [Text]
connectorMetadata :: Maybe ConnectorMetadata
connectorLabel :: Maybe Text
connectorDescription :: Maybe Text
connectorArn :: Maybe Text
canUseAsSource :: Maybe Bool
canUseAsDestination :: Maybe Bool
authenticationConfig :: Maybe AuthenticationConfig
$sel:supportedWriteOperations:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [WriteOperationType]
$sel:supportedTriggerTypes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [TriggerType]
$sel:supportedSchedulingFrequencies:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ScheduleFrequencyType]
$sel:supportedOperators:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Operators]
$sel:supportedDestinationConnectors:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorType]
$sel:supportedApiVersions:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
$sel:registeredBy:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:registeredAt:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe POSIX
$sel:logoURL:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:isPrivateLinkEndpointUrlRequired:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:isPrivateLinkEnabled:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:connectorVersion:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorType
$sel:connectorRuntimeSettings:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [ConnectorRuntimeSetting]
$sel:connectorProvisioningType:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningType
$sel:connectorProvisioningConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorProvisioningConfig
$sel:connectorOwner:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorName:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorModes:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe [Text]
$sel:connectorMetadata:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe ConnectorMetadata
$sel:connectorLabel:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorDescription:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:connectorArn:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Text
$sel:canUseAsSource:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:canUseAsDestination:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe Bool
$sel:authenticationConfig:ConnectorConfiguration' :: ConnectorConfiguration -> Maybe AuthenticationConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationConfig
authenticationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
canUseAsDestination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
canUseAsSource
      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
connectorLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorMetadata
connectorMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
connectorModes
      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 Text
connectorOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorProvisioningConfig
connectorProvisioningConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorProvisioningType
connectorProvisioningType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConnectorRuntimeSetting]
connectorRuntimeSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorType
connectorType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isPrivateLinkEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
isPrivateLinkEndpointUrlRequired
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logoURL
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
registeredAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
registeredBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
supportedApiVersions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [ConnectorType]
supportedDestinationConnectors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Operators]
supportedOperators
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [ScheduleFrequencyType]
supportedSchedulingFrequencies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [TriggerType]
supportedTriggerTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [WriteOperationType]
supportedWriteOperations