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

import Amazonka.AppFlow.Types.AmplitudeConnectorProfileCredentials
import Amazonka.AppFlow.Types.CustomConnectorProfileCredentials
import Amazonka.AppFlow.Types.DatadogConnectorProfileCredentials
import Amazonka.AppFlow.Types.DynatraceConnectorProfileCredentials
import Amazonka.AppFlow.Types.GoogleAnalyticsConnectorProfileCredentials
import Amazonka.AppFlow.Types.HoneycodeConnectorProfileCredentials
import Amazonka.AppFlow.Types.InforNexusConnectorProfileCredentials
import Amazonka.AppFlow.Types.MarketoConnectorProfileCredentials
import Amazonka.AppFlow.Types.RedshiftConnectorProfileCredentials
import Amazonka.AppFlow.Types.SAPODataConnectorProfileCredentials
import Amazonka.AppFlow.Types.SalesforceConnectorProfileCredentials
import Amazonka.AppFlow.Types.ServiceNowConnectorProfileCredentials
import Amazonka.AppFlow.Types.SingularConnectorProfileCredentials
import Amazonka.AppFlow.Types.SlackConnectorProfileCredentials
import Amazonka.AppFlow.Types.SnowflakeConnectorProfileCredentials
import Amazonka.AppFlow.Types.TrendmicroConnectorProfileCredentials
import Amazonka.AppFlow.Types.VeevaConnectorProfileCredentials
import Amazonka.AppFlow.Types.ZendeskConnectorProfileCredentials
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 credentials required by a connector.
--
-- /See:/ 'newConnectorProfileCredentials' smart constructor.
data ConnectorProfileCredentials = ConnectorProfileCredentials'
  { -- | The connector-specific credentials required when using Amplitude.
    ConnectorProfileCredentials
-> Maybe AmplitudeConnectorProfileCredentials
amplitude :: Prelude.Maybe AmplitudeConnectorProfileCredentials,
    ConnectorProfileCredentials
-> Maybe CustomConnectorProfileCredentials
customConnector :: Prelude.Maybe CustomConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Datadog.
    ConnectorProfileCredentials
-> Maybe DatadogConnectorProfileCredentials
datadog :: Prelude.Maybe DatadogConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Dynatrace.
    ConnectorProfileCredentials
-> Maybe DynatraceConnectorProfileCredentials
dynatrace :: Prelude.Maybe DynatraceConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Google Analytics.
    ConnectorProfileCredentials
-> Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics :: Prelude.Maybe GoogleAnalyticsConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Amazon Honeycode.
    ConnectorProfileCredentials
-> Maybe HoneycodeConnectorProfileCredentials
honeycode :: Prelude.Maybe HoneycodeConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Infor Nexus.
    ConnectorProfileCredentials
-> Maybe InforNexusConnectorProfileCredentials
inforNexus :: Prelude.Maybe InforNexusConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Marketo.
    ConnectorProfileCredentials
-> Maybe MarketoConnectorProfileCredentials
marketo :: Prelude.Maybe MarketoConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Amazon Redshift.
    ConnectorProfileCredentials
-> Maybe RedshiftConnectorProfileCredentials
redshift :: Prelude.Maybe RedshiftConnectorProfileCredentials,
    ConnectorProfileCredentials
-> Maybe SAPODataConnectorProfileCredentials
sAPOData :: Prelude.Maybe SAPODataConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Salesforce.
    ConnectorProfileCredentials
-> Maybe SalesforceConnectorProfileCredentials
salesforce :: Prelude.Maybe SalesforceConnectorProfileCredentials,
    -- | The connector-specific credentials required when using ServiceNow.
    ConnectorProfileCredentials
-> Maybe ServiceNowConnectorProfileCredentials
serviceNow :: Prelude.Maybe ServiceNowConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Singular.
    ConnectorProfileCredentials
-> Maybe SingularConnectorProfileCredentials
singular :: Prelude.Maybe SingularConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Slack.
    ConnectorProfileCredentials
-> Maybe SlackConnectorProfileCredentials
slack :: Prelude.Maybe SlackConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Snowflake.
    ConnectorProfileCredentials
-> Maybe SnowflakeConnectorProfileCredentials
snowflake :: Prelude.Maybe SnowflakeConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Trend Micro.
    ConnectorProfileCredentials
-> Maybe TrendmicroConnectorProfileCredentials
trendmicro :: Prelude.Maybe TrendmicroConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Veeva.
    ConnectorProfileCredentials
-> Maybe VeevaConnectorProfileCredentials
veeva :: Prelude.Maybe VeevaConnectorProfileCredentials,
    -- | The connector-specific credentials required when using Zendesk.
    ConnectorProfileCredentials
-> Maybe ZendeskConnectorProfileCredentials
zendesk :: Prelude.Maybe ZendeskConnectorProfileCredentials
  }
  deriving (ConnectorProfileCredentials -> ConnectorProfileCredentials -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectorProfileCredentials -> ConnectorProfileCredentials -> Bool
$c/= :: ConnectorProfileCredentials -> ConnectorProfileCredentials -> Bool
== :: ConnectorProfileCredentials -> ConnectorProfileCredentials -> Bool
$c== :: ConnectorProfileCredentials -> ConnectorProfileCredentials -> Bool
Prelude.Eq, Int -> ConnectorProfileCredentials -> ShowS
[ConnectorProfileCredentials] -> ShowS
ConnectorProfileCredentials -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectorProfileCredentials] -> ShowS
$cshowList :: [ConnectorProfileCredentials] -> ShowS
show :: ConnectorProfileCredentials -> String
$cshow :: ConnectorProfileCredentials -> String
showsPrec :: Int -> ConnectorProfileCredentials -> ShowS
$cshowsPrec :: Int -> ConnectorProfileCredentials -> ShowS
Prelude.Show, forall x.
Rep ConnectorProfileCredentials x -> ConnectorProfileCredentials
forall x.
ConnectorProfileCredentials -> Rep ConnectorProfileCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConnectorProfileCredentials x -> ConnectorProfileCredentials
$cfrom :: forall x.
ConnectorProfileCredentials -> Rep ConnectorProfileCredentials x
Prelude.Generic)

-- |
-- Create a value of 'ConnectorProfileCredentials' 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', 'connectorProfileCredentials_amplitude' - The connector-specific credentials required when using Amplitude.
--
-- 'customConnector', 'connectorProfileCredentials_customConnector' - Undocumented member.
--
-- 'datadog', 'connectorProfileCredentials_datadog' - The connector-specific credentials required when using Datadog.
--
-- 'dynatrace', 'connectorProfileCredentials_dynatrace' - The connector-specific credentials required when using Dynatrace.
--
-- 'googleAnalytics', 'connectorProfileCredentials_googleAnalytics' - The connector-specific credentials required when using Google Analytics.
--
-- 'honeycode', 'connectorProfileCredentials_honeycode' - The connector-specific credentials required when using Amazon Honeycode.
--
-- 'inforNexus', 'connectorProfileCredentials_inforNexus' - The connector-specific credentials required when using Infor Nexus.
--
-- 'marketo', 'connectorProfileCredentials_marketo' - The connector-specific credentials required when using Marketo.
--
-- 'redshift', 'connectorProfileCredentials_redshift' - The connector-specific credentials required when using Amazon Redshift.
--
-- 'sAPOData', 'connectorProfileCredentials_sAPOData' - Undocumented member.
--
-- 'salesforce', 'connectorProfileCredentials_salesforce' - The connector-specific credentials required when using Salesforce.
--
-- 'serviceNow', 'connectorProfileCredentials_serviceNow' - The connector-specific credentials required when using ServiceNow.
--
-- 'singular', 'connectorProfileCredentials_singular' - The connector-specific credentials required when using Singular.
--
-- 'slack', 'connectorProfileCredentials_slack' - The connector-specific credentials required when using Slack.
--
-- 'snowflake', 'connectorProfileCredentials_snowflake' - The connector-specific credentials required when using Snowflake.
--
-- 'trendmicro', 'connectorProfileCredentials_trendmicro' - The connector-specific credentials required when using Trend Micro.
--
-- 'veeva', 'connectorProfileCredentials_veeva' - The connector-specific credentials required when using Veeva.
--
-- 'zendesk', 'connectorProfileCredentials_zendesk' - The connector-specific credentials required when using Zendesk.
newConnectorProfileCredentials ::
  ConnectorProfileCredentials
newConnectorProfileCredentials :: ConnectorProfileCredentials
newConnectorProfileCredentials =
  ConnectorProfileCredentials'
    { $sel:amplitude:ConnectorProfileCredentials' :: Maybe AmplitudeConnectorProfileCredentials
amplitude =
        forall a. Maybe a
Prelude.Nothing,
      $sel:customConnector:ConnectorProfileCredentials' :: Maybe CustomConnectorProfileCredentials
customConnector = forall a. Maybe a
Prelude.Nothing,
      $sel:datadog:ConnectorProfileCredentials' :: Maybe DatadogConnectorProfileCredentials
datadog = forall a. Maybe a
Prelude.Nothing,
      $sel:dynatrace:ConnectorProfileCredentials' :: Maybe DynatraceConnectorProfileCredentials
dynatrace = forall a. Maybe a
Prelude.Nothing,
      $sel:googleAnalytics:ConnectorProfileCredentials' :: Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics = forall a. Maybe a
Prelude.Nothing,
      $sel:honeycode:ConnectorProfileCredentials' :: Maybe HoneycodeConnectorProfileCredentials
honeycode = forall a. Maybe a
Prelude.Nothing,
      $sel:inforNexus:ConnectorProfileCredentials' :: Maybe InforNexusConnectorProfileCredentials
inforNexus = forall a. Maybe a
Prelude.Nothing,
      $sel:marketo:ConnectorProfileCredentials' :: Maybe MarketoConnectorProfileCredentials
marketo = forall a. Maybe a
Prelude.Nothing,
      $sel:redshift:ConnectorProfileCredentials' :: Maybe RedshiftConnectorProfileCredentials
redshift = forall a. Maybe a
Prelude.Nothing,
      $sel:sAPOData:ConnectorProfileCredentials' :: Maybe SAPODataConnectorProfileCredentials
sAPOData = forall a. Maybe a
Prelude.Nothing,
      $sel:salesforce:ConnectorProfileCredentials' :: Maybe SalesforceConnectorProfileCredentials
salesforce = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceNow:ConnectorProfileCredentials' :: Maybe ServiceNowConnectorProfileCredentials
serviceNow = forall a. Maybe a
Prelude.Nothing,
      $sel:singular:ConnectorProfileCredentials' :: Maybe SingularConnectorProfileCredentials
singular = forall a. Maybe a
Prelude.Nothing,
      $sel:slack:ConnectorProfileCredentials' :: Maybe SlackConnectorProfileCredentials
slack = forall a. Maybe a
Prelude.Nothing,
      $sel:snowflake:ConnectorProfileCredentials' :: Maybe SnowflakeConnectorProfileCredentials
snowflake = forall a. Maybe a
Prelude.Nothing,
      $sel:trendmicro:ConnectorProfileCredentials' :: Maybe TrendmicroConnectorProfileCredentials
trendmicro = forall a. Maybe a
Prelude.Nothing,
      $sel:veeva:ConnectorProfileCredentials' :: Maybe VeevaConnectorProfileCredentials
veeva = forall a. Maybe a
Prelude.Nothing,
      $sel:zendesk:ConnectorProfileCredentials' :: Maybe ZendeskConnectorProfileCredentials
zendesk = forall a. Maybe a
Prelude.Nothing
    }

-- | The connector-specific credentials required when using Amplitude.
connectorProfileCredentials_amplitude :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe AmplitudeConnectorProfileCredentials)
connectorProfileCredentials_amplitude :: Lens'
  ConnectorProfileCredentials
  (Maybe AmplitudeConnectorProfileCredentials)
connectorProfileCredentials_amplitude = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe AmplitudeConnectorProfileCredentials
amplitude :: Maybe AmplitudeConnectorProfileCredentials
$sel:amplitude:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe AmplitudeConnectorProfileCredentials
amplitude} -> Maybe AmplitudeConnectorProfileCredentials
amplitude) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe AmplitudeConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:amplitude:ConnectorProfileCredentials' :: Maybe AmplitudeConnectorProfileCredentials
amplitude = Maybe AmplitudeConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | Undocumented member.
connectorProfileCredentials_customConnector :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe CustomConnectorProfileCredentials)
connectorProfileCredentials_customConnector :: Lens'
  ConnectorProfileCredentials
  (Maybe CustomConnectorProfileCredentials)
connectorProfileCredentials_customConnector = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe CustomConnectorProfileCredentials
customConnector :: Maybe CustomConnectorProfileCredentials
$sel:customConnector:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe CustomConnectorProfileCredentials
customConnector} -> Maybe CustomConnectorProfileCredentials
customConnector) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe CustomConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:customConnector:ConnectorProfileCredentials' :: Maybe CustomConnectorProfileCredentials
customConnector = Maybe CustomConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Datadog.
connectorProfileCredentials_datadog :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe DatadogConnectorProfileCredentials)
connectorProfileCredentials_datadog :: Lens'
  ConnectorProfileCredentials
  (Maybe DatadogConnectorProfileCredentials)
connectorProfileCredentials_datadog = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe DatadogConnectorProfileCredentials
datadog :: Maybe DatadogConnectorProfileCredentials
$sel:datadog:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DatadogConnectorProfileCredentials
datadog} -> Maybe DatadogConnectorProfileCredentials
datadog) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe DatadogConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:datadog:ConnectorProfileCredentials' :: Maybe DatadogConnectorProfileCredentials
datadog = Maybe DatadogConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Dynatrace.
connectorProfileCredentials_dynatrace :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe DynatraceConnectorProfileCredentials)
connectorProfileCredentials_dynatrace :: Lens'
  ConnectorProfileCredentials
  (Maybe DynatraceConnectorProfileCredentials)
connectorProfileCredentials_dynatrace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe DynatraceConnectorProfileCredentials
dynatrace :: Maybe DynatraceConnectorProfileCredentials
$sel:dynatrace:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DynatraceConnectorProfileCredentials
dynatrace} -> Maybe DynatraceConnectorProfileCredentials
dynatrace) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe DynatraceConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:dynatrace:ConnectorProfileCredentials' :: Maybe DynatraceConnectorProfileCredentials
dynatrace = Maybe DynatraceConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Google Analytics.
connectorProfileCredentials_googleAnalytics :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe GoogleAnalyticsConnectorProfileCredentials)
connectorProfileCredentials_googleAnalytics :: Lens'
  ConnectorProfileCredentials
  (Maybe GoogleAnalyticsConnectorProfileCredentials)
connectorProfileCredentials_googleAnalytics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileCredentials
$sel:googleAnalytics:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics} -> Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe GoogleAnalyticsConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:googleAnalytics:ConnectorProfileCredentials' :: Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics = Maybe GoogleAnalyticsConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Amazon Honeycode.
connectorProfileCredentials_honeycode :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe HoneycodeConnectorProfileCredentials)
connectorProfileCredentials_honeycode :: Lens'
  ConnectorProfileCredentials
  (Maybe HoneycodeConnectorProfileCredentials)
connectorProfileCredentials_honeycode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe HoneycodeConnectorProfileCredentials
honeycode :: Maybe HoneycodeConnectorProfileCredentials
$sel:honeycode:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe HoneycodeConnectorProfileCredentials
honeycode} -> Maybe HoneycodeConnectorProfileCredentials
honeycode) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe HoneycodeConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:honeycode:ConnectorProfileCredentials' :: Maybe HoneycodeConnectorProfileCredentials
honeycode = Maybe HoneycodeConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Infor Nexus.
connectorProfileCredentials_inforNexus :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe InforNexusConnectorProfileCredentials)
connectorProfileCredentials_inforNexus :: Lens'
  ConnectorProfileCredentials
  (Maybe InforNexusConnectorProfileCredentials)
connectorProfileCredentials_inforNexus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe InforNexusConnectorProfileCredentials
inforNexus :: Maybe InforNexusConnectorProfileCredentials
$sel:inforNexus:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe InforNexusConnectorProfileCredentials
inforNexus} -> Maybe InforNexusConnectorProfileCredentials
inforNexus) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe InforNexusConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:inforNexus:ConnectorProfileCredentials' :: Maybe InforNexusConnectorProfileCredentials
inforNexus = Maybe InforNexusConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Marketo.
connectorProfileCredentials_marketo :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe MarketoConnectorProfileCredentials)
connectorProfileCredentials_marketo :: Lens'
  ConnectorProfileCredentials
  (Maybe MarketoConnectorProfileCredentials)
connectorProfileCredentials_marketo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe MarketoConnectorProfileCredentials
marketo :: Maybe MarketoConnectorProfileCredentials
$sel:marketo:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe MarketoConnectorProfileCredentials
marketo} -> Maybe MarketoConnectorProfileCredentials
marketo) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe MarketoConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:marketo:ConnectorProfileCredentials' :: Maybe MarketoConnectorProfileCredentials
marketo = Maybe MarketoConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Amazon Redshift.
connectorProfileCredentials_redshift :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe RedshiftConnectorProfileCredentials)
connectorProfileCredentials_redshift :: Lens'
  ConnectorProfileCredentials
  (Maybe RedshiftConnectorProfileCredentials)
connectorProfileCredentials_redshift = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe RedshiftConnectorProfileCredentials
redshift :: Maybe RedshiftConnectorProfileCredentials
$sel:redshift:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe RedshiftConnectorProfileCredentials
redshift} -> Maybe RedshiftConnectorProfileCredentials
redshift) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe RedshiftConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:redshift:ConnectorProfileCredentials' :: Maybe RedshiftConnectorProfileCredentials
redshift = Maybe RedshiftConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

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

-- | The connector-specific credentials required when using Salesforce.
connectorProfileCredentials_salesforce :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe SalesforceConnectorProfileCredentials)
connectorProfileCredentials_salesforce :: Lens'
  ConnectorProfileCredentials
  (Maybe SalesforceConnectorProfileCredentials)
connectorProfileCredentials_salesforce = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe SalesforceConnectorProfileCredentials
salesforce :: Maybe SalesforceConnectorProfileCredentials
$sel:salesforce:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SalesforceConnectorProfileCredentials
salesforce} -> Maybe SalesforceConnectorProfileCredentials
salesforce) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe SalesforceConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:salesforce:ConnectorProfileCredentials' :: Maybe SalesforceConnectorProfileCredentials
salesforce = Maybe SalesforceConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using ServiceNow.
connectorProfileCredentials_serviceNow :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe ServiceNowConnectorProfileCredentials)
connectorProfileCredentials_serviceNow :: Lens'
  ConnectorProfileCredentials
  (Maybe ServiceNowConnectorProfileCredentials)
connectorProfileCredentials_serviceNow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe ServiceNowConnectorProfileCredentials
serviceNow :: Maybe ServiceNowConnectorProfileCredentials
$sel:serviceNow:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ServiceNowConnectorProfileCredentials
serviceNow} -> Maybe ServiceNowConnectorProfileCredentials
serviceNow) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe ServiceNowConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:serviceNow:ConnectorProfileCredentials' :: Maybe ServiceNowConnectorProfileCredentials
serviceNow = Maybe ServiceNowConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Singular.
connectorProfileCredentials_singular :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe SingularConnectorProfileCredentials)
connectorProfileCredentials_singular :: Lens'
  ConnectorProfileCredentials
  (Maybe SingularConnectorProfileCredentials)
connectorProfileCredentials_singular = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe SingularConnectorProfileCredentials
singular :: Maybe SingularConnectorProfileCredentials
$sel:singular:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SingularConnectorProfileCredentials
singular} -> Maybe SingularConnectorProfileCredentials
singular) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe SingularConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:singular:ConnectorProfileCredentials' :: Maybe SingularConnectorProfileCredentials
singular = Maybe SingularConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Slack.
connectorProfileCredentials_slack :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe SlackConnectorProfileCredentials)
connectorProfileCredentials_slack :: Lens'
  ConnectorProfileCredentials
  (Maybe SlackConnectorProfileCredentials)
connectorProfileCredentials_slack = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe SlackConnectorProfileCredentials
slack :: Maybe SlackConnectorProfileCredentials
$sel:slack:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SlackConnectorProfileCredentials
slack} -> Maybe SlackConnectorProfileCredentials
slack) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe SlackConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:slack:ConnectorProfileCredentials' :: Maybe SlackConnectorProfileCredentials
slack = Maybe SlackConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Snowflake.
connectorProfileCredentials_snowflake :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe SnowflakeConnectorProfileCredentials)
connectorProfileCredentials_snowflake :: Lens'
  ConnectorProfileCredentials
  (Maybe SnowflakeConnectorProfileCredentials)
connectorProfileCredentials_snowflake = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe SnowflakeConnectorProfileCredentials
snowflake :: Maybe SnowflakeConnectorProfileCredentials
$sel:snowflake:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SnowflakeConnectorProfileCredentials
snowflake} -> Maybe SnowflakeConnectorProfileCredentials
snowflake) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe SnowflakeConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:snowflake:ConnectorProfileCredentials' :: Maybe SnowflakeConnectorProfileCredentials
snowflake = Maybe SnowflakeConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Trend Micro.
connectorProfileCredentials_trendmicro :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe TrendmicroConnectorProfileCredentials)
connectorProfileCredentials_trendmicro :: Lens'
  ConnectorProfileCredentials
  (Maybe TrendmicroConnectorProfileCredentials)
connectorProfileCredentials_trendmicro = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe TrendmicroConnectorProfileCredentials
trendmicro :: Maybe TrendmicroConnectorProfileCredentials
$sel:trendmicro:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe TrendmicroConnectorProfileCredentials
trendmicro} -> Maybe TrendmicroConnectorProfileCredentials
trendmicro) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe TrendmicroConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:trendmicro:ConnectorProfileCredentials' :: Maybe TrendmicroConnectorProfileCredentials
trendmicro = Maybe TrendmicroConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Veeva.
connectorProfileCredentials_veeva :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe VeevaConnectorProfileCredentials)
connectorProfileCredentials_veeva :: Lens'
  ConnectorProfileCredentials
  (Maybe VeevaConnectorProfileCredentials)
connectorProfileCredentials_veeva = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe VeevaConnectorProfileCredentials
veeva :: Maybe VeevaConnectorProfileCredentials
$sel:veeva:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe VeevaConnectorProfileCredentials
veeva} -> Maybe VeevaConnectorProfileCredentials
veeva) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe VeevaConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:veeva:ConnectorProfileCredentials' :: Maybe VeevaConnectorProfileCredentials
veeva = Maybe VeevaConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

-- | The connector-specific credentials required when using Zendesk.
connectorProfileCredentials_zendesk :: Lens.Lens' ConnectorProfileCredentials (Prelude.Maybe ZendeskConnectorProfileCredentials)
connectorProfileCredentials_zendesk :: Lens'
  ConnectorProfileCredentials
  (Maybe ZendeskConnectorProfileCredentials)
connectorProfileCredentials_zendesk = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfileCredentials' {Maybe ZendeskConnectorProfileCredentials
zendesk :: Maybe ZendeskConnectorProfileCredentials
$sel:zendesk:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ZendeskConnectorProfileCredentials
zendesk} -> Maybe ZendeskConnectorProfileCredentials
zendesk) (\s :: ConnectorProfileCredentials
s@ConnectorProfileCredentials' {} Maybe ZendeskConnectorProfileCredentials
a -> ConnectorProfileCredentials
s {$sel:zendesk:ConnectorProfileCredentials' :: Maybe ZendeskConnectorProfileCredentials
zendesk = Maybe ZendeskConnectorProfileCredentials
a} :: ConnectorProfileCredentials)

instance Prelude.Hashable ConnectorProfileCredentials where
  hashWithSalt :: Int -> ConnectorProfileCredentials -> Int
hashWithSalt Int
_salt ConnectorProfileCredentials' {Maybe AmplitudeConnectorProfileCredentials
Maybe DatadogConnectorProfileCredentials
Maybe DynatraceConnectorProfileCredentials
Maybe GoogleAnalyticsConnectorProfileCredentials
Maybe HoneycodeConnectorProfileCredentials
Maybe InforNexusConnectorProfileCredentials
Maybe MarketoConnectorProfileCredentials
Maybe CustomConnectorProfileCredentials
Maybe RedshiftConnectorProfileCredentials
Maybe SAPODataConnectorProfileCredentials
Maybe SalesforceConnectorProfileCredentials
Maybe ServiceNowConnectorProfileCredentials
Maybe SingularConnectorProfileCredentials
Maybe SlackConnectorProfileCredentials
Maybe SnowflakeConnectorProfileCredentials
Maybe TrendmicroConnectorProfileCredentials
Maybe VeevaConnectorProfileCredentials
Maybe ZendeskConnectorProfileCredentials
zendesk :: Maybe ZendeskConnectorProfileCredentials
veeva :: Maybe VeevaConnectorProfileCredentials
trendmicro :: Maybe TrendmicroConnectorProfileCredentials
snowflake :: Maybe SnowflakeConnectorProfileCredentials
slack :: Maybe SlackConnectorProfileCredentials
singular :: Maybe SingularConnectorProfileCredentials
serviceNow :: Maybe ServiceNowConnectorProfileCredentials
salesforce :: Maybe SalesforceConnectorProfileCredentials
sAPOData :: Maybe SAPODataConnectorProfileCredentials
redshift :: Maybe RedshiftConnectorProfileCredentials
marketo :: Maybe MarketoConnectorProfileCredentials
inforNexus :: Maybe InforNexusConnectorProfileCredentials
honeycode :: Maybe HoneycodeConnectorProfileCredentials
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileCredentials
dynatrace :: Maybe DynatraceConnectorProfileCredentials
datadog :: Maybe DatadogConnectorProfileCredentials
customConnector :: Maybe CustomConnectorProfileCredentials
amplitude :: Maybe AmplitudeConnectorProfileCredentials
$sel:zendesk:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ZendeskConnectorProfileCredentials
$sel:veeva:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe VeevaConnectorProfileCredentials
$sel:trendmicro:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe TrendmicroConnectorProfileCredentials
$sel:snowflake:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SnowflakeConnectorProfileCredentials
$sel:slack:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SlackConnectorProfileCredentials
$sel:singular:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SingularConnectorProfileCredentials
$sel:serviceNow:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ServiceNowConnectorProfileCredentials
$sel:salesforce:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SalesforceConnectorProfileCredentials
$sel:sAPOData:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SAPODataConnectorProfileCredentials
$sel:redshift:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe RedshiftConnectorProfileCredentials
$sel:marketo:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe MarketoConnectorProfileCredentials
$sel:inforNexus:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe InforNexusConnectorProfileCredentials
$sel:honeycode:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe HoneycodeConnectorProfileCredentials
$sel:googleAnalytics:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe GoogleAnalyticsConnectorProfileCredentials
$sel:dynatrace:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DynatraceConnectorProfileCredentials
$sel:datadog:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DatadogConnectorProfileCredentials
$sel:customConnector:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe CustomConnectorProfileCredentials
$sel:amplitude:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe AmplitudeConnectorProfileCredentials
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AmplitudeConnectorProfileCredentials
amplitude
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomConnectorProfileCredentials
customConnector
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DatadogConnectorProfileCredentials
datadog
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DynatraceConnectorProfileCredentials
dynatrace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HoneycodeConnectorProfileCredentials
honeycode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InforNexusConnectorProfileCredentials
inforNexus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MarketoConnectorProfileCredentials
marketo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RedshiftConnectorProfileCredentials
redshift
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SAPODataConnectorProfileCredentials
sAPOData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SalesforceConnectorProfileCredentials
salesforce
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServiceNowConnectorProfileCredentials
serviceNow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SingularConnectorProfileCredentials
singular
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SlackConnectorProfileCredentials
slack
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnowflakeConnectorProfileCredentials
snowflake
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrendmicroConnectorProfileCredentials
trendmicro
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VeevaConnectorProfileCredentials
veeva
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ZendeskConnectorProfileCredentials
zendesk

instance Prelude.NFData ConnectorProfileCredentials where
  rnf :: ConnectorProfileCredentials -> ()
rnf ConnectorProfileCredentials' {Maybe AmplitudeConnectorProfileCredentials
Maybe DatadogConnectorProfileCredentials
Maybe DynatraceConnectorProfileCredentials
Maybe GoogleAnalyticsConnectorProfileCredentials
Maybe HoneycodeConnectorProfileCredentials
Maybe InforNexusConnectorProfileCredentials
Maybe MarketoConnectorProfileCredentials
Maybe CustomConnectorProfileCredentials
Maybe RedshiftConnectorProfileCredentials
Maybe SAPODataConnectorProfileCredentials
Maybe SalesforceConnectorProfileCredentials
Maybe ServiceNowConnectorProfileCredentials
Maybe SingularConnectorProfileCredentials
Maybe SlackConnectorProfileCredentials
Maybe SnowflakeConnectorProfileCredentials
Maybe TrendmicroConnectorProfileCredentials
Maybe VeevaConnectorProfileCredentials
Maybe ZendeskConnectorProfileCredentials
zendesk :: Maybe ZendeskConnectorProfileCredentials
veeva :: Maybe VeevaConnectorProfileCredentials
trendmicro :: Maybe TrendmicroConnectorProfileCredentials
snowflake :: Maybe SnowflakeConnectorProfileCredentials
slack :: Maybe SlackConnectorProfileCredentials
singular :: Maybe SingularConnectorProfileCredentials
serviceNow :: Maybe ServiceNowConnectorProfileCredentials
salesforce :: Maybe SalesforceConnectorProfileCredentials
sAPOData :: Maybe SAPODataConnectorProfileCredentials
redshift :: Maybe RedshiftConnectorProfileCredentials
marketo :: Maybe MarketoConnectorProfileCredentials
inforNexus :: Maybe InforNexusConnectorProfileCredentials
honeycode :: Maybe HoneycodeConnectorProfileCredentials
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileCredentials
dynatrace :: Maybe DynatraceConnectorProfileCredentials
datadog :: Maybe DatadogConnectorProfileCredentials
customConnector :: Maybe CustomConnectorProfileCredentials
amplitude :: Maybe AmplitudeConnectorProfileCredentials
$sel:zendesk:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ZendeskConnectorProfileCredentials
$sel:veeva:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe VeevaConnectorProfileCredentials
$sel:trendmicro:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe TrendmicroConnectorProfileCredentials
$sel:snowflake:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SnowflakeConnectorProfileCredentials
$sel:slack:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SlackConnectorProfileCredentials
$sel:singular:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SingularConnectorProfileCredentials
$sel:serviceNow:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ServiceNowConnectorProfileCredentials
$sel:salesforce:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SalesforceConnectorProfileCredentials
$sel:sAPOData:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SAPODataConnectorProfileCredentials
$sel:redshift:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe RedshiftConnectorProfileCredentials
$sel:marketo:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe MarketoConnectorProfileCredentials
$sel:inforNexus:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe InforNexusConnectorProfileCredentials
$sel:honeycode:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe HoneycodeConnectorProfileCredentials
$sel:googleAnalytics:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe GoogleAnalyticsConnectorProfileCredentials
$sel:dynatrace:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DynatraceConnectorProfileCredentials
$sel:datadog:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DatadogConnectorProfileCredentials
$sel:customConnector:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe CustomConnectorProfileCredentials
$sel:amplitude:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe AmplitudeConnectorProfileCredentials
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AmplitudeConnectorProfileCredentials
amplitude
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomConnectorProfileCredentials
customConnector
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatadogConnectorProfileCredentials
datadog
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DynatraceConnectorProfileCredentials
dynatrace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GoogleAnalyticsConnectorProfileCredentials
googleAnalytics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HoneycodeConnectorProfileCredentials
honeycode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InforNexusConnectorProfileCredentials
inforNexus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MarketoConnectorProfileCredentials
marketo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RedshiftConnectorProfileCredentials
redshift
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SAPODataConnectorProfileCredentials
sAPOData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SalesforceConnectorProfileCredentials
salesforce
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceNowConnectorProfileCredentials
serviceNow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SingularConnectorProfileCredentials
singular
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SlackConnectorProfileCredentials
slack
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SnowflakeConnectorProfileCredentials
snowflake
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrendmicroConnectorProfileCredentials
trendmicro
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VeevaConnectorProfileCredentials
veeva
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ZendeskConnectorProfileCredentials
zendesk

instance Data.ToJSON ConnectorProfileCredentials where
  toJSON :: ConnectorProfileCredentials -> Value
toJSON ConnectorProfileCredentials' {Maybe AmplitudeConnectorProfileCredentials
Maybe DatadogConnectorProfileCredentials
Maybe DynatraceConnectorProfileCredentials
Maybe GoogleAnalyticsConnectorProfileCredentials
Maybe HoneycodeConnectorProfileCredentials
Maybe InforNexusConnectorProfileCredentials
Maybe MarketoConnectorProfileCredentials
Maybe CustomConnectorProfileCredentials
Maybe RedshiftConnectorProfileCredentials
Maybe SAPODataConnectorProfileCredentials
Maybe SalesforceConnectorProfileCredentials
Maybe ServiceNowConnectorProfileCredentials
Maybe SingularConnectorProfileCredentials
Maybe SlackConnectorProfileCredentials
Maybe SnowflakeConnectorProfileCredentials
Maybe TrendmicroConnectorProfileCredentials
Maybe VeevaConnectorProfileCredentials
Maybe ZendeskConnectorProfileCredentials
zendesk :: Maybe ZendeskConnectorProfileCredentials
veeva :: Maybe VeevaConnectorProfileCredentials
trendmicro :: Maybe TrendmicroConnectorProfileCredentials
snowflake :: Maybe SnowflakeConnectorProfileCredentials
slack :: Maybe SlackConnectorProfileCredentials
singular :: Maybe SingularConnectorProfileCredentials
serviceNow :: Maybe ServiceNowConnectorProfileCredentials
salesforce :: Maybe SalesforceConnectorProfileCredentials
sAPOData :: Maybe SAPODataConnectorProfileCredentials
redshift :: Maybe RedshiftConnectorProfileCredentials
marketo :: Maybe MarketoConnectorProfileCredentials
inforNexus :: Maybe InforNexusConnectorProfileCredentials
honeycode :: Maybe HoneycodeConnectorProfileCredentials
googleAnalytics :: Maybe GoogleAnalyticsConnectorProfileCredentials
dynatrace :: Maybe DynatraceConnectorProfileCredentials
datadog :: Maybe DatadogConnectorProfileCredentials
customConnector :: Maybe CustomConnectorProfileCredentials
amplitude :: Maybe AmplitudeConnectorProfileCredentials
$sel:zendesk:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ZendeskConnectorProfileCredentials
$sel:veeva:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe VeevaConnectorProfileCredentials
$sel:trendmicro:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe TrendmicroConnectorProfileCredentials
$sel:snowflake:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SnowflakeConnectorProfileCredentials
$sel:slack:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SlackConnectorProfileCredentials
$sel:singular:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SingularConnectorProfileCredentials
$sel:serviceNow:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe ServiceNowConnectorProfileCredentials
$sel:salesforce:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SalesforceConnectorProfileCredentials
$sel:sAPOData:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe SAPODataConnectorProfileCredentials
$sel:redshift:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe RedshiftConnectorProfileCredentials
$sel:marketo:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe MarketoConnectorProfileCredentials
$sel:inforNexus:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe InforNexusConnectorProfileCredentials
$sel:honeycode:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe HoneycodeConnectorProfileCredentials
$sel:googleAnalytics:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe GoogleAnalyticsConnectorProfileCredentials
$sel:dynatrace:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DynatraceConnectorProfileCredentials
$sel:datadog:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe DatadogConnectorProfileCredentials
$sel:customConnector:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe CustomConnectorProfileCredentials
$sel:amplitude:ConnectorProfileCredentials' :: ConnectorProfileCredentials
-> Maybe AmplitudeConnectorProfileCredentials
..} =
    [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 AmplitudeConnectorProfileCredentials
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 CustomConnectorProfileCredentials
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 DatadogConnectorProfileCredentials
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 DynatraceConnectorProfileCredentials
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 GoogleAnalyticsConnectorProfileCredentials
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 HoneycodeConnectorProfileCredentials
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 InforNexusConnectorProfileCredentials
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 MarketoConnectorProfileCredentials
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 RedshiftConnectorProfileCredentials
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 SAPODataConnectorProfileCredentials
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 SalesforceConnectorProfileCredentials
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 ServiceNowConnectorProfileCredentials
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 SingularConnectorProfileCredentials
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 SlackConnectorProfileCredentials
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 SnowflakeConnectorProfileCredentials
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 TrendmicroConnectorProfileCredentials
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 VeevaConnectorProfileCredentials
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 ZendeskConnectorProfileCredentials
zendesk
          ]
      )