{-# 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.ConnectorProfileProperties
-- 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.ConnectorProfileProperties where

import Amazonka.AppFlow.Types.AmplitudeConnectorProfileProperties
import Amazonka.AppFlow.Types.CustomConnectorProfileProperties
import Amazonka.AppFlow.Types.DatadogConnectorProfileProperties
import Amazonka.AppFlow.Types.DynatraceConnectorProfileProperties
import Amazonka.AppFlow.Types.GoogleAnalyticsConnectorProfileProperties
import Amazonka.AppFlow.Types.HoneycodeConnectorProfileProperties
import Amazonka.AppFlow.Types.InforNexusConnectorProfileProperties
import Amazonka.AppFlow.Types.MarketoConnectorProfileProperties
import Amazonka.AppFlow.Types.RedshiftConnectorProfileProperties
import Amazonka.AppFlow.Types.SAPODataConnectorProfileProperties
import Amazonka.AppFlow.Types.SalesforceConnectorProfileProperties
import Amazonka.AppFlow.Types.ServiceNowConnectorProfileProperties
import Amazonka.AppFlow.Types.SingularConnectorProfileProperties
import Amazonka.AppFlow.Types.SlackConnectorProfileProperties
import Amazonka.AppFlow.Types.SnowflakeConnectorProfileProperties
import Amazonka.AppFlow.Types.TrendmicroConnectorProfileProperties
import Amazonka.AppFlow.Types.VeevaConnectorProfileProperties
import Amazonka.AppFlow.Types.ZendeskConnectorProfileProperties
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 connector-specific profile properties required by each connector.
--
-- /See:/ 'newConnectorProfileProperties' smart constructor.
data ConnectorProfileProperties = ConnectorProfileProperties'
  { -- | The connector-specific properties required by Amplitude.
    ConnectorProfileProperties
-> Maybe AmplitudeConnectorProfileProperties
amplitude :: Prelude.Maybe AmplitudeConnectorProfileProperties,
    -- | The properties required by the custom connector.
    ConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
customConnector :: Prelude.Maybe CustomConnectorProfileProperties,
    -- | The connector-specific properties required by Datadog.
    ConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
datadog :: Prelude.Maybe DatadogConnectorProfileProperties,
    -- | The connector-specific properties required by Dynatrace.
    ConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
dynatrace :: Prelude.Maybe DynatraceConnectorProfileProperties,
    -- | The connector-specific properties required Google Analytics.
    ConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics :: Prelude.Maybe GoogleAnalyticsConnectorProfileProperties,
    -- | The connector-specific properties required by Amazon Honeycode.
    ConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
honeycode :: Prelude.Maybe HoneycodeConnectorProfileProperties,
    -- | The connector-specific properties required by Infor Nexus.
    ConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
inforNexus :: Prelude.Maybe InforNexusConnectorProfileProperties,
    -- | The connector-specific properties required by Marketo.
    ConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
marketo :: Prelude.Maybe MarketoConnectorProfileProperties,
    -- | The connector-specific properties required by Amazon Redshift.
    ConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
redshift :: Prelude.Maybe RedshiftConnectorProfileProperties,
    ConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
sAPOData :: Prelude.Maybe SAPODataConnectorProfileProperties,
    -- | The connector-specific properties required by Salesforce.
    ConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
salesforce :: Prelude.Maybe SalesforceConnectorProfileProperties,
    -- | The connector-specific properties required by serviceNow.
    ConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
serviceNow :: Prelude.Maybe ServiceNowConnectorProfileProperties,
    -- | The connector-specific properties required by Singular.
    ConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
singular :: Prelude.Maybe SingularConnectorProfileProperties,
    -- | The connector-specific properties required by Slack.
    ConnectorProfileProperties -> Maybe SlackConnectorProfileProperties
slack :: Prelude.Maybe SlackConnectorProfileProperties,
    -- | The connector-specific properties required by Snowflake.
    ConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
snowflake :: Prelude.Maybe SnowflakeConnectorProfileProperties,
    -- | The connector-specific properties required by Trend Micro.
    ConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
trendmicro :: Prelude.Maybe TrendmicroConnectorProfileProperties,
    -- | The connector-specific properties required by Veeva.
    ConnectorProfileProperties -> Maybe VeevaConnectorProfileProperties
veeva :: Prelude.Maybe VeevaConnectorProfileProperties,
    -- | The connector-specific properties required by Zendesk.
    ConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
zendesk :: Prelude.Maybe ZendeskConnectorProfileProperties
  }
  deriving (ConnectorProfileProperties -> ConnectorProfileProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectorProfileProperties -> ConnectorProfileProperties -> Bool
$c/= :: ConnectorProfileProperties -> ConnectorProfileProperties -> Bool
== :: ConnectorProfileProperties -> ConnectorProfileProperties -> Bool
$c== :: ConnectorProfileProperties -> ConnectorProfileProperties -> Bool
Prelude.Eq, ReadPrec [ConnectorProfileProperties]
ReadPrec ConnectorProfileProperties
Int -> ReadS ConnectorProfileProperties
ReadS [ConnectorProfileProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConnectorProfileProperties]
$creadListPrec :: ReadPrec [ConnectorProfileProperties]
readPrec :: ReadPrec ConnectorProfileProperties
$creadPrec :: ReadPrec ConnectorProfileProperties
readList :: ReadS [ConnectorProfileProperties]
$creadList :: ReadS [ConnectorProfileProperties]
readsPrec :: Int -> ReadS ConnectorProfileProperties
$creadsPrec :: Int -> ReadS ConnectorProfileProperties
Prelude.Read, Int -> ConnectorProfileProperties -> ShowS
[ConnectorProfileProperties] -> ShowS
ConnectorProfileProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectorProfileProperties] -> ShowS
$cshowList :: [ConnectorProfileProperties] -> ShowS
show :: ConnectorProfileProperties -> String
$cshow :: ConnectorProfileProperties -> String
showsPrec :: Int -> ConnectorProfileProperties -> ShowS
$cshowsPrec :: Int -> ConnectorProfileProperties -> ShowS
Prelude.Show, forall x.
Rep ConnectorProfileProperties x -> ConnectorProfileProperties
forall x.
ConnectorProfileProperties -> Rep ConnectorProfileProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConnectorProfileProperties x -> ConnectorProfileProperties
$cfrom :: forall x.
ConnectorProfileProperties -> Rep ConnectorProfileProperties x
Prelude.Generic)

-- |
-- Create a value of 'ConnectorProfileProperties' 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:
--
-- 'amplitude', 'connectorProfileProperties_amplitude' - The connector-specific properties required by Amplitude.
--
-- 'customConnector', 'connectorProfileProperties_customConnector' - The properties required by the custom connector.
--
-- 'datadog', 'connectorProfileProperties_datadog' - The connector-specific properties required by Datadog.
--
-- 'dynatrace', 'connectorProfileProperties_dynatrace' - The connector-specific properties required by Dynatrace.
--
-- 'googleAnalytics', 'connectorProfileProperties_googleAnalytics' - The connector-specific properties required Google Analytics.
--
-- 'honeycode', 'connectorProfileProperties_honeycode' - The connector-specific properties required by Amazon Honeycode.
--
-- 'inforNexus', 'connectorProfileProperties_inforNexus' - The connector-specific properties required by Infor Nexus.
--
-- 'marketo', 'connectorProfileProperties_marketo' - The connector-specific properties required by Marketo.
--
-- 'redshift', 'connectorProfileProperties_redshift' - The connector-specific properties required by Amazon Redshift.
--
-- 'sAPOData', 'connectorProfileProperties_sAPOData' - Undocumented member.
--
-- 'salesforce', 'connectorProfileProperties_salesforce' - The connector-specific properties required by Salesforce.
--
-- 'serviceNow', 'connectorProfileProperties_serviceNow' - The connector-specific properties required by serviceNow.
--
-- 'singular', 'connectorProfileProperties_singular' - The connector-specific properties required by Singular.
--
-- 'slack', 'connectorProfileProperties_slack' - The connector-specific properties required by Slack.
--
-- 'snowflake', 'connectorProfileProperties_snowflake' - The connector-specific properties required by Snowflake.
--
-- 'trendmicro', 'connectorProfileProperties_trendmicro' - The connector-specific properties required by Trend Micro.
--
-- 'veeva', 'connectorProfileProperties_veeva' - The connector-specific properties required by Veeva.
--
-- 'zendesk', 'connectorProfileProperties_zendesk' - The connector-specific properties required by Zendesk.
newConnectorProfileProperties ::
  ConnectorProfileProperties
newConnectorProfileProperties :: ConnectorProfileProperties
newConnectorProfileProperties =
  ConnectorProfileProperties'
    { $sel:amplitude:ConnectorProfileProperties' :: Maybe AmplitudeConnectorProfileProperties
amplitude =
        forall a. Maybe a
Prelude.Nothing,
      $sel:customConnector:ConnectorProfileProperties' :: Maybe CustomConnectorProfileProperties
customConnector = forall a. Maybe a
Prelude.Nothing,
      $sel:datadog:ConnectorProfileProperties' :: Maybe DatadogConnectorProfileProperties
datadog = forall a. Maybe a
Prelude.Nothing,
      $sel:dynatrace:ConnectorProfileProperties' :: Maybe DynatraceConnectorProfileProperties
dynatrace = forall a. Maybe a
Prelude.Nothing,
      $sel:googleAnalytics:ConnectorProfileProperties' :: Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics = forall a. Maybe a
Prelude.Nothing,
      $sel:honeycode:ConnectorProfileProperties' :: Maybe HoneycodeConnectorProfileProperties
honeycode = forall a. Maybe a
Prelude.Nothing,
      $sel:inforNexus:ConnectorProfileProperties' :: Maybe InforNexusConnectorProfileProperties
inforNexus = forall a. Maybe a
Prelude.Nothing,
      $sel:marketo:ConnectorProfileProperties' :: Maybe MarketoConnectorProfileProperties
marketo = forall a. Maybe a
Prelude.Nothing,
      $sel:redshift:ConnectorProfileProperties' :: Maybe RedshiftConnectorProfileProperties
redshift = forall a. Maybe a
Prelude.Nothing,
      $sel:sAPOData:ConnectorProfileProperties' :: Maybe SAPODataConnectorProfileProperties
sAPOData = forall a. Maybe a
Prelude.Nothing,
      $sel:salesforce:ConnectorProfileProperties' :: Maybe SalesforceConnectorProfileProperties
salesforce = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceNow:ConnectorProfileProperties' :: Maybe ServiceNowConnectorProfileProperties
serviceNow = forall a. Maybe a
Prelude.Nothing,
      $sel:singular:ConnectorProfileProperties' :: Maybe SingularConnectorProfileProperties
singular = forall a. Maybe a
Prelude.Nothing,
      $sel:slack:ConnectorProfileProperties' :: Maybe SlackConnectorProfileProperties
slack = forall a. Maybe a
Prelude.Nothing,
      $sel:snowflake:ConnectorProfileProperties' :: Maybe SnowflakeConnectorProfileProperties
snowflake = forall a. Maybe a
Prelude.Nothing,
      $sel:trendmicro:ConnectorProfileProperties' :: Maybe TrendmicroConnectorProfileProperties
trendmicro = forall a. Maybe a
Prelude.Nothing,
      $sel:veeva:ConnectorProfileProperties' :: Maybe VeevaConnectorProfileProperties
veeva = forall a. Maybe a
Prelude.Nothing,
      $sel:zendesk:ConnectorProfileProperties' :: Maybe ZendeskConnectorProfileProperties
zendesk = forall a. Maybe a
Prelude.Nothing
    }

-- | The connector-specific properties required by Amplitude.
connectorProfileProperties_amplitude :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe AmplitudeConnectorProfileProperties)
connectorProfileProperties_amplitude :: Lens'
  ConnectorProfileProperties
  (Maybe AmplitudeConnectorProfileProperties)
connectorProfileProperties_amplitude = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe AmplitudeConnectorProfileProperties
amplitude :: Maybe AmplitudeConnectorProfileProperties
$sel:amplitude:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe AmplitudeConnectorProfileProperties
amplitude} -> Maybe AmplitudeConnectorProfileProperties
amplitude) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe AmplitudeConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:amplitude:ConnectorProfileProperties' :: Maybe AmplitudeConnectorProfileProperties
amplitude = Maybe AmplitudeConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The properties required by the custom connector.
connectorProfileProperties_customConnector :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe CustomConnectorProfileProperties)
connectorProfileProperties_customConnector :: Lens'
  ConnectorProfileProperties (Maybe CustomConnectorProfileProperties)
connectorProfileProperties_customConnector = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe CustomConnectorProfileProperties
customConnector :: Maybe CustomConnectorProfileProperties
$sel:customConnector:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
customConnector} -> Maybe CustomConnectorProfileProperties
customConnector) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe CustomConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:customConnector:ConnectorProfileProperties' :: Maybe CustomConnectorProfileProperties
customConnector = Maybe CustomConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Datadog.
connectorProfileProperties_datadog :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe DatadogConnectorProfileProperties)
connectorProfileProperties_datadog :: Lens'
  ConnectorProfileProperties
  (Maybe DatadogConnectorProfileProperties)
connectorProfileProperties_datadog = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe DatadogConnectorProfileProperties
datadog :: Maybe DatadogConnectorProfileProperties
$sel:datadog:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
datadog} -> Maybe DatadogConnectorProfileProperties
datadog) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe DatadogConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:datadog:ConnectorProfileProperties' :: Maybe DatadogConnectorProfileProperties
datadog = Maybe DatadogConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Dynatrace.
connectorProfileProperties_dynatrace :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe DynatraceConnectorProfileProperties)
connectorProfileProperties_dynatrace :: Lens'
  ConnectorProfileProperties
  (Maybe DynatraceConnectorProfileProperties)
connectorProfileProperties_dynatrace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe DynatraceConnectorProfileProperties
dynatrace :: Maybe DynatraceConnectorProfileProperties
$sel:dynatrace:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
dynatrace} -> Maybe DynatraceConnectorProfileProperties
dynatrace) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe DynatraceConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:dynatrace:ConnectorProfileProperties' :: Maybe DynatraceConnectorProfileProperties
dynatrace = Maybe DynatraceConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required Google Analytics.
connectorProfileProperties_googleAnalytics :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe GoogleAnalyticsConnectorProfileProperties)
connectorProfileProperties_googleAnalytics :: Lens'
  ConnectorProfileProperties
  (Maybe GoogleAnalyticsConnectorProfileProperties)
connectorProfileProperties_googleAnalytics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileProperties
$sel:googleAnalytics:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics} -> Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe GoogleAnalyticsConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:googleAnalytics:ConnectorProfileProperties' :: Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics = Maybe GoogleAnalyticsConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Amazon Honeycode.
connectorProfileProperties_honeycode :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe HoneycodeConnectorProfileProperties)
connectorProfileProperties_honeycode :: Lens'
  ConnectorProfileProperties
  (Maybe HoneycodeConnectorProfileProperties)
connectorProfileProperties_honeycode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe HoneycodeConnectorProfileProperties
honeycode :: Maybe HoneycodeConnectorProfileProperties
$sel:honeycode:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
honeycode} -> Maybe HoneycodeConnectorProfileProperties
honeycode) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe HoneycodeConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:honeycode:ConnectorProfileProperties' :: Maybe HoneycodeConnectorProfileProperties
honeycode = Maybe HoneycodeConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Infor Nexus.
connectorProfileProperties_inforNexus :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe InforNexusConnectorProfileProperties)
connectorProfileProperties_inforNexus :: Lens'
  ConnectorProfileProperties
  (Maybe InforNexusConnectorProfileProperties)
connectorProfileProperties_inforNexus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe InforNexusConnectorProfileProperties
inforNexus :: Maybe InforNexusConnectorProfileProperties
$sel:inforNexus:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
inforNexus} -> Maybe InforNexusConnectorProfileProperties
inforNexus) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe InforNexusConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:inforNexus:ConnectorProfileProperties' :: Maybe InforNexusConnectorProfileProperties
inforNexus = Maybe InforNexusConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Marketo.
connectorProfileProperties_marketo :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe MarketoConnectorProfileProperties)
connectorProfileProperties_marketo :: Lens'
  ConnectorProfileProperties
  (Maybe MarketoConnectorProfileProperties)
connectorProfileProperties_marketo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe MarketoConnectorProfileProperties
marketo :: Maybe MarketoConnectorProfileProperties
$sel:marketo:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
marketo} -> Maybe MarketoConnectorProfileProperties
marketo) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe MarketoConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:marketo:ConnectorProfileProperties' :: Maybe MarketoConnectorProfileProperties
marketo = Maybe MarketoConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Amazon Redshift.
connectorProfileProperties_redshift :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe RedshiftConnectorProfileProperties)
connectorProfileProperties_redshift :: Lens'
  ConnectorProfileProperties
  (Maybe RedshiftConnectorProfileProperties)
connectorProfileProperties_redshift = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe RedshiftConnectorProfileProperties
redshift :: Maybe RedshiftConnectorProfileProperties
$sel:redshift:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
redshift} -> Maybe RedshiftConnectorProfileProperties
redshift) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe RedshiftConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:redshift:ConnectorProfileProperties' :: Maybe RedshiftConnectorProfileProperties
redshift = Maybe RedshiftConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | Undocumented member.
connectorProfileProperties_sAPOData :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe SAPODataConnectorProfileProperties)
connectorProfileProperties_sAPOData :: Lens'
  ConnectorProfileProperties
  (Maybe SAPODataConnectorProfileProperties)
connectorProfileProperties_sAPOData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe SAPODataConnectorProfileProperties
sAPOData :: Maybe SAPODataConnectorProfileProperties
$sel:sAPOData:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
sAPOData} -> Maybe SAPODataConnectorProfileProperties
sAPOData) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe SAPODataConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:sAPOData:ConnectorProfileProperties' :: Maybe SAPODataConnectorProfileProperties
sAPOData = Maybe SAPODataConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Salesforce.
connectorProfileProperties_salesforce :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe SalesforceConnectorProfileProperties)
connectorProfileProperties_salesforce :: Lens'
  ConnectorProfileProperties
  (Maybe SalesforceConnectorProfileProperties)
connectorProfileProperties_salesforce = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe SalesforceConnectorProfileProperties
salesforce :: Maybe SalesforceConnectorProfileProperties
$sel:salesforce:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
salesforce} -> Maybe SalesforceConnectorProfileProperties
salesforce) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe SalesforceConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:salesforce:ConnectorProfileProperties' :: Maybe SalesforceConnectorProfileProperties
salesforce = Maybe SalesforceConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by serviceNow.
connectorProfileProperties_serviceNow :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe ServiceNowConnectorProfileProperties)
connectorProfileProperties_serviceNow :: Lens'
  ConnectorProfileProperties
  (Maybe ServiceNowConnectorProfileProperties)
connectorProfileProperties_serviceNow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe ServiceNowConnectorProfileProperties
serviceNow :: Maybe ServiceNowConnectorProfileProperties
$sel:serviceNow:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
serviceNow} -> Maybe ServiceNowConnectorProfileProperties
serviceNow) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe ServiceNowConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:serviceNow:ConnectorProfileProperties' :: Maybe ServiceNowConnectorProfileProperties
serviceNow = Maybe ServiceNowConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Singular.
connectorProfileProperties_singular :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe SingularConnectorProfileProperties)
connectorProfileProperties_singular :: Lens'
  ConnectorProfileProperties
  (Maybe SingularConnectorProfileProperties)
connectorProfileProperties_singular = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe SingularConnectorProfileProperties
singular :: Maybe SingularConnectorProfileProperties
$sel:singular:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
singular} -> Maybe SingularConnectorProfileProperties
singular) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe SingularConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:singular:ConnectorProfileProperties' :: Maybe SingularConnectorProfileProperties
singular = Maybe SingularConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Slack.
connectorProfileProperties_slack :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe SlackConnectorProfileProperties)
connectorProfileProperties_slack :: Lens'
  ConnectorProfileProperties (Maybe SlackConnectorProfileProperties)
connectorProfileProperties_slack = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe SlackConnectorProfileProperties
slack :: Maybe SlackConnectorProfileProperties
$sel:slack:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe SlackConnectorProfileProperties
slack} -> Maybe SlackConnectorProfileProperties
slack) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe SlackConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:slack:ConnectorProfileProperties' :: Maybe SlackConnectorProfileProperties
slack = Maybe SlackConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Snowflake.
connectorProfileProperties_snowflake :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe SnowflakeConnectorProfileProperties)
connectorProfileProperties_snowflake :: Lens'
  ConnectorProfileProperties
  (Maybe SnowflakeConnectorProfileProperties)
connectorProfileProperties_snowflake = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe SnowflakeConnectorProfileProperties
snowflake :: Maybe SnowflakeConnectorProfileProperties
$sel:snowflake:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
snowflake} -> Maybe SnowflakeConnectorProfileProperties
snowflake) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe SnowflakeConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:snowflake:ConnectorProfileProperties' :: Maybe SnowflakeConnectorProfileProperties
snowflake = Maybe SnowflakeConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Trend Micro.
connectorProfileProperties_trendmicro :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe TrendmicroConnectorProfileProperties)
connectorProfileProperties_trendmicro :: Lens'
  ConnectorProfileProperties
  (Maybe TrendmicroConnectorProfileProperties)
connectorProfileProperties_trendmicro = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe TrendmicroConnectorProfileProperties
trendmicro :: Maybe TrendmicroConnectorProfileProperties
$sel:trendmicro:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
trendmicro} -> Maybe TrendmicroConnectorProfileProperties
trendmicro) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe TrendmicroConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:trendmicro:ConnectorProfileProperties' :: Maybe TrendmicroConnectorProfileProperties
trendmicro = Maybe TrendmicroConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Veeva.
connectorProfileProperties_veeva :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe VeevaConnectorProfileProperties)
connectorProfileProperties_veeva :: Lens'
  ConnectorProfileProperties (Maybe VeevaConnectorProfileProperties)
connectorProfileProperties_veeva = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe VeevaConnectorProfileProperties
veeva :: Maybe VeevaConnectorProfileProperties
$sel:veeva:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe VeevaConnectorProfileProperties
veeva} -> Maybe VeevaConnectorProfileProperties
veeva) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe VeevaConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:veeva:ConnectorProfileProperties' :: Maybe VeevaConnectorProfileProperties
veeva = Maybe VeevaConnectorProfileProperties
a} :: ConnectorProfileProperties)

-- | The connector-specific properties required by Zendesk.
connectorProfileProperties_zendesk :: Lens.Lens' ConnectorProfileProperties (Prelude.Maybe ZendeskConnectorProfileProperties)
connectorProfileProperties_zendesk :: Lens'
  ConnectorProfileProperties
  (Maybe ZendeskConnectorProfileProperties)
connectorProfileProperties_zendesk = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileProperties' {Maybe ZendeskConnectorProfileProperties
zendesk :: Maybe ZendeskConnectorProfileProperties
$sel:zendesk:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
zendesk} -> Maybe ZendeskConnectorProfileProperties
zendesk) (\s :: ConnectorProfileProperties
s@ConnectorProfileProperties' {} Maybe ZendeskConnectorProfileProperties
a -> ConnectorProfileProperties
s {$sel:zendesk:ConnectorProfileProperties' :: Maybe ZendeskConnectorProfileProperties
zendesk = Maybe ZendeskConnectorProfileProperties
a} :: ConnectorProfileProperties)

instance Data.FromJSON ConnectorProfileProperties where
  parseJSON :: Value -> Parser ConnectorProfileProperties
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ConnectorProfileProperties"
      ( \Object
x ->
          Maybe AmplitudeConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
-> Maybe SlackConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
-> Maybe VeevaConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
-> ConnectorProfileProperties
ConnectorProfileProperties'
            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
"Amplitude")
            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
"CustomConnector")
            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
"Datadog")
            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
"Dynatrace")
            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
"GoogleAnalytics")
            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
"Honeycode")
            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
"InforNexus")
            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
"Marketo")
            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
"Redshift")
            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
"SAPOData")
            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
"Salesforce")
            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
"ServiceNow")
            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
"Singular")
            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
"Slack")
            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
"Snowflake")
            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
"Trendmicro")
            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
"Veeva")
            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
"Zendesk")
      )

instance Prelude.Hashable ConnectorProfileProperties where
  hashWithSalt :: Int -> ConnectorProfileProperties -> Int
hashWithSalt Int
_salt ConnectorProfileProperties' {Maybe AmplitudeConnectorProfileProperties
Maybe DatadogConnectorProfileProperties
Maybe DynatraceConnectorProfileProperties
Maybe GoogleAnalyticsConnectorProfileProperties
Maybe HoneycodeConnectorProfileProperties
Maybe InforNexusConnectorProfileProperties
Maybe MarketoConnectorProfileProperties
Maybe CustomConnectorProfileProperties
Maybe RedshiftConnectorProfileProperties
Maybe SAPODataConnectorProfileProperties
Maybe SalesforceConnectorProfileProperties
Maybe ServiceNowConnectorProfileProperties
Maybe SingularConnectorProfileProperties
Maybe SlackConnectorProfileProperties
Maybe SnowflakeConnectorProfileProperties
Maybe TrendmicroConnectorProfileProperties
Maybe VeevaConnectorProfileProperties
Maybe ZendeskConnectorProfileProperties
zendesk :: Maybe ZendeskConnectorProfileProperties
veeva :: Maybe VeevaConnectorProfileProperties
trendmicro :: Maybe TrendmicroConnectorProfileProperties
snowflake :: Maybe SnowflakeConnectorProfileProperties
slack :: Maybe SlackConnectorProfileProperties
singular :: Maybe SingularConnectorProfileProperties
serviceNow :: Maybe ServiceNowConnectorProfileProperties
salesforce :: Maybe SalesforceConnectorProfileProperties
sAPOData :: Maybe SAPODataConnectorProfileProperties
redshift :: Maybe RedshiftConnectorProfileProperties
marketo :: Maybe MarketoConnectorProfileProperties
inforNexus :: Maybe InforNexusConnectorProfileProperties
honeycode :: Maybe HoneycodeConnectorProfileProperties
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileProperties
dynatrace :: Maybe DynatraceConnectorProfileProperties
datadog :: Maybe DatadogConnectorProfileProperties
customConnector :: Maybe CustomConnectorProfileProperties
amplitude :: Maybe AmplitudeConnectorProfileProperties
$sel:zendesk:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
$sel:veeva:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe VeevaConnectorProfileProperties
$sel:trendmicro:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
$sel:snowflake:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
$sel:slack:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe SlackConnectorProfileProperties
$sel:singular:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
$sel:serviceNow:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
$sel:salesforce:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
$sel:sAPOData:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
$sel:redshift:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
$sel:marketo:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
$sel:inforNexus:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
$sel:honeycode:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
$sel:googleAnalytics:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
$sel:dynatrace:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
$sel:datadog:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
$sel:customConnector:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
$sel:amplitude:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe AmplitudeConnectorProfileProperties
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AmplitudeConnectorProfileProperties
amplitude
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomConnectorProfileProperties
customConnector
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DatadogConnectorProfileProperties
datadog
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DynatraceConnectorProfileProperties
dynatrace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HoneycodeConnectorProfileProperties
honeycode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InforNexusConnectorProfileProperties
inforNexus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MarketoConnectorProfileProperties
marketo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RedshiftConnectorProfileProperties
redshift
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SAPODataConnectorProfileProperties
sAPOData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SalesforceConnectorProfileProperties
salesforce
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServiceNowConnectorProfileProperties
serviceNow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SingularConnectorProfileProperties
singular
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SlackConnectorProfileProperties
slack
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnowflakeConnectorProfileProperties
snowflake
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrendmicroConnectorProfileProperties
trendmicro
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VeevaConnectorProfileProperties
veeva
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ZendeskConnectorProfileProperties
zendesk

instance Prelude.NFData ConnectorProfileProperties where
  rnf :: ConnectorProfileProperties -> ()
rnf ConnectorProfileProperties' {Maybe AmplitudeConnectorProfileProperties
Maybe DatadogConnectorProfileProperties
Maybe DynatraceConnectorProfileProperties
Maybe GoogleAnalyticsConnectorProfileProperties
Maybe HoneycodeConnectorProfileProperties
Maybe InforNexusConnectorProfileProperties
Maybe MarketoConnectorProfileProperties
Maybe CustomConnectorProfileProperties
Maybe RedshiftConnectorProfileProperties
Maybe SAPODataConnectorProfileProperties
Maybe SalesforceConnectorProfileProperties
Maybe ServiceNowConnectorProfileProperties
Maybe SingularConnectorProfileProperties
Maybe SlackConnectorProfileProperties
Maybe SnowflakeConnectorProfileProperties
Maybe TrendmicroConnectorProfileProperties
Maybe VeevaConnectorProfileProperties
Maybe ZendeskConnectorProfileProperties
zendesk :: Maybe ZendeskConnectorProfileProperties
veeva :: Maybe VeevaConnectorProfileProperties
trendmicro :: Maybe TrendmicroConnectorProfileProperties
snowflake :: Maybe SnowflakeConnectorProfileProperties
slack :: Maybe SlackConnectorProfileProperties
singular :: Maybe SingularConnectorProfileProperties
serviceNow :: Maybe ServiceNowConnectorProfileProperties
salesforce :: Maybe SalesforceConnectorProfileProperties
sAPOData :: Maybe SAPODataConnectorProfileProperties
redshift :: Maybe RedshiftConnectorProfileProperties
marketo :: Maybe MarketoConnectorProfileProperties
inforNexus :: Maybe InforNexusConnectorProfileProperties
honeycode :: Maybe HoneycodeConnectorProfileProperties
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileProperties
dynatrace :: Maybe DynatraceConnectorProfileProperties
datadog :: Maybe DatadogConnectorProfileProperties
customConnector :: Maybe CustomConnectorProfileProperties
amplitude :: Maybe AmplitudeConnectorProfileProperties
$sel:zendesk:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
$sel:veeva:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe VeevaConnectorProfileProperties
$sel:trendmicro:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
$sel:snowflake:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
$sel:slack:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe SlackConnectorProfileProperties
$sel:singular:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
$sel:serviceNow:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
$sel:salesforce:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
$sel:sAPOData:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
$sel:redshift:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
$sel:marketo:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
$sel:inforNexus:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
$sel:honeycode:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
$sel:googleAnalytics:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
$sel:dynatrace:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
$sel:datadog:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
$sel:customConnector:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
$sel:amplitude:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe AmplitudeConnectorProfileProperties
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AmplitudeConnectorProfileProperties
amplitude
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomConnectorProfileProperties
customConnector
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatadogConnectorProfileProperties
datadog
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DynatraceConnectorProfileProperties
dynatrace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HoneycodeConnectorProfileProperties
honeycode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InforNexusConnectorProfileProperties
inforNexus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MarketoConnectorProfileProperties
marketo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RedshiftConnectorProfileProperties
redshift
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SAPODataConnectorProfileProperties
sAPOData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SalesforceConnectorProfileProperties
salesforce
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceNowConnectorProfileProperties
serviceNow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SingularConnectorProfileProperties
singular
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SlackConnectorProfileProperties
slack
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SnowflakeConnectorProfileProperties
snowflake
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrendmicroConnectorProfileProperties
trendmicro
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VeevaConnectorProfileProperties
veeva
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ZendeskConnectorProfileProperties
zendesk

instance Data.ToJSON ConnectorProfileProperties where
  toJSON :: ConnectorProfileProperties -> Value
toJSON ConnectorProfileProperties' {Maybe AmplitudeConnectorProfileProperties
Maybe DatadogConnectorProfileProperties
Maybe DynatraceConnectorProfileProperties
Maybe GoogleAnalyticsConnectorProfileProperties
Maybe HoneycodeConnectorProfileProperties
Maybe InforNexusConnectorProfileProperties
Maybe MarketoConnectorProfileProperties
Maybe CustomConnectorProfileProperties
Maybe RedshiftConnectorProfileProperties
Maybe SAPODataConnectorProfileProperties
Maybe SalesforceConnectorProfileProperties
Maybe ServiceNowConnectorProfileProperties
Maybe SingularConnectorProfileProperties
Maybe SlackConnectorProfileProperties
Maybe SnowflakeConnectorProfileProperties
Maybe TrendmicroConnectorProfileProperties
Maybe VeevaConnectorProfileProperties
Maybe ZendeskConnectorProfileProperties
zendesk :: Maybe ZendeskConnectorProfileProperties
veeva :: Maybe VeevaConnectorProfileProperties
trendmicro :: Maybe TrendmicroConnectorProfileProperties
snowflake :: Maybe SnowflakeConnectorProfileProperties
slack :: Maybe SlackConnectorProfileProperties
singular :: Maybe SingularConnectorProfileProperties
serviceNow :: Maybe ServiceNowConnectorProfileProperties
salesforce :: Maybe SalesforceConnectorProfileProperties
sAPOData :: Maybe SAPODataConnectorProfileProperties
redshift :: Maybe RedshiftConnectorProfileProperties
marketo :: Maybe MarketoConnectorProfileProperties
inforNexus :: Maybe InforNexusConnectorProfileProperties
honeycode :: Maybe HoneycodeConnectorProfileProperties
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileProperties
dynatrace :: Maybe DynatraceConnectorProfileProperties
datadog :: Maybe DatadogConnectorProfileProperties
customConnector :: Maybe CustomConnectorProfileProperties
amplitude :: Maybe AmplitudeConnectorProfileProperties
$sel:zendesk:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ZendeskConnectorProfileProperties
$sel:veeva:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe VeevaConnectorProfileProperties
$sel:trendmicro:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe TrendmicroConnectorProfileProperties
$sel:snowflake:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SnowflakeConnectorProfileProperties
$sel:slack:ConnectorProfileProperties' :: ConnectorProfileProperties -> Maybe SlackConnectorProfileProperties
$sel:singular:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SingularConnectorProfileProperties
$sel:serviceNow:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe ServiceNowConnectorProfileProperties
$sel:salesforce:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SalesforceConnectorProfileProperties
$sel:sAPOData:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe SAPODataConnectorProfileProperties
$sel:redshift:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe RedshiftConnectorProfileProperties
$sel:marketo:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe MarketoConnectorProfileProperties
$sel:inforNexus:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe InforNexusConnectorProfileProperties
$sel:honeycode:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe HoneycodeConnectorProfileProperties
$sel:googleAnalytics:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe GoogleAnalyticsConnectorProfileProperties
$sel:dynatrace:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DynatraceConnectorProfileProperties
$sel:datadog:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe DatadogConnectorProfileProperties
$sel:customConnector:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe CustomConnectorProfileProperties
$sel:amplitude:ConnectorProfileProperties' :: ConnectorProfileProperties
-> Maybe AmplitudeConnectorProfileProperties
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Amplitude" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AmplitudeConnectorProfileProperties
amplitude,
            (Key
"CustomConnector" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomConnectorProfileProperties
customConnector,
            (Key
"Datadog" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DatadogConnectorProfileProperties
datadog,
            (Key
"Dynatrace" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DynatraceConnectorProfileProperties
dynatrace,
            (Key
"GoogleAnalytics" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GoogleAnalyticsConnectorProfileProperties
googleAnalytics,
            (Key
"Honeycode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HoneycodeConnectorProfileProperties
honeycode,
            (Key
"InforNexus" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InforNexusConnectorProfileProperties
inforNexus,
            (Key
"Marketo" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MarketoConnectorProfileProperties
marketo,
            (Key
"Redshift" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftConnectorProfileProperties
redshift,
            (Key
"SAPOData" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SAPODataConnectorProfileProperties
sAPOData,
            (Key
"Salesforce" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceConnectorProfileProperties
salesforce,
            (Key
"ServiceNow" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ServiceNowConnectorProfileProperties
serviceNow,
            (Key
"Singular" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SingularConnectorProfileProperties
singular,
            (Key
"Slack" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SlackConnectorProfileProperties
slack,
            (Key
"Snowflake" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeConnectorProfileProperties
snowflake,
            (Key
"Trendmicro" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TrendmicroConnectorProfileProperties
trendmicro,
            (Key
"Veeva" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VeevaConnectorProfileProperties
veeva,
            (Key
"Zendesk" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ZendeskConnectorProfileProperties
zendesk
          ]
      )