module Stratosphere.Kendra.DataSource.SalesforceConfigurationProperty (
        module Exports, SalesforceConfigurationProperty(..),
        mkSalesforceConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceChatterFeedConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceKnowledgeArticleConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceStandardObjectAttachmentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceStandardObjectConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SalesforceConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html>
    SalesforceConfigurationProperty {SalesforceConfigurationProperty -> ()
haddock_workaround_ :: (),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-chatterfeedconfiguration>
                                     SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
chatterFeedConfiguration :: (Prelude.Maybe SalesforceChatterFeedConfigurationProperty),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-crawlattachments>
                                     SalesforceConfigurationProperty -> Maybe (Value Bool)
crawlAttachments :: (Prelude.Maybe (Value Prelude.Bool)),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-excludeattachmentfilepatterns>
                                     SalesforceConfigurationProperty -> Maybe (ValueList Text)
excludeAttachmentFilePatterns :: (Prelude.Maybe (ValueList Prelude.Text)),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-includeattachmentfilepatterns>
                                     SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: (Prelude.Maybe (ValueList Prelude.Text)),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-knowledgearticleconfiguration>
                                     SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
knowledgeArticleConfiguration :: (Prelude.Maybe SalesforceKnowledgeArticleConfigurationProperty),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-secretarn>
                                     SalesforceConfigurationProperty -> Value Text
secretArn :: (Value Prelude.Text),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-serverurl>
                                     SalesforceConfigurationProperty -> Value Text
serverUrl :: (Value Prelude.Text),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-standardobjectattachmentconfiguration>
                                     SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectAttachmentConfiguration :: (Prelude.Maybe SalesforceStandardObjectAttachmentConfigurationProperty),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceconfiguration.html#cfn-kendra-datasource-salesforceconfiguration-standardobjectconfigurations>
                                     SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
standardObjectConfigurations :: (Prelude.Maybe [SalesforceStandardObjectConfigurationProperty])}
  deriving stock (SalesforceConfigurationProperty
-> SalesforceConfigurationProperty -> Bool
(SalesforceConfigurationProperty
 -> SalesforceConfigurationProperty -> Bool)
-> (SalesforceConfigurationProperty
    -> SalesforceConfigurationProperty -> Bool)
-> Eq SalesforceConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SalesforceConfigurationProperty
-> SalesforceConfigurationProperty -> Bool
== :: SalesforceConfigurationProperty
-> SalesforceConfigurationProperty -> Bool
$c/= :: SalesforceConfigurationProperty
-> SalesforceConfigurationProperty -> Bool
/= :: SalesforceConfigurationProperty
-> SalesforceConfigurationProperty -> Bool
Prelude.Eq, Int -> SalesforceConfigurationProperty -> ShowS
[SalesforceConfigurationProperty] -> ShowS
SalesforceConfigurationProperty -> String
(Int -> SalesforceConfigurationProperty -> ShowS)
-> (SalesforceConfigurationProperty -> String)
-> ([SalesforceConfigurationProperty] -> ShowS)
-> Show SalesforceConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SalesforceConfigurationProperty -> ShowS
showsPrec :: Int -> SalesforceConfigurationProperty -> ShowS
$cshow :: SalesforceConfigurationProperty -> String
show :: SalesforceConfigurationProperty -> String
$cshowList :: [SalesforceConfigurationProperty] -> ShowS
showList :: [SalesforceConfigurationProperty] -> ShowS
Prelude.Show)
mkSalesforceConfigurationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> SalesforceConfigurationProperty
mkSalesforceConfigurationProperty :: Value Text -> Value Text -> SalesforceConfigurationProperty
mkSalesforceConfigurationProperty Value Text
secretArn Value Text
serverUrl
  = SalesforceConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), secretArn :: Value Text
secretArn = Value Text
secretArn,
       serverUrl :: Value Text
serverUrl = Value Text
serverUrl, chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
chatterFeedConfiguration = Maybe SalesforceChatterFeedConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       crawlAttachments :: Maybe (Value Bool)
crawlAttachments = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       excludeAttachmentFilePatterns :: Maybe (ValueList Text)
excludeAttachmentFilePatterns = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       includeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
knowledgeArticleConfiguration = Maybe SalesforceKnowledgeArticleConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectAttachmentConfiguration = Maybe SalesforceStandardObjectAttachmentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
standardObjectConfigurations = Maybe [SalesforceStandardObjectConfigurationProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SalesforceConfigurationProperty where
  toResourceProperties :: SalesforceConfigurationProperty -> ResourceProperties
toResourceProperties SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Kendra::DataSource.SalesforceConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
                           [Key
"SecretArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
secretArn, Key
"ServerUrl" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
serverUrl]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> SalesforceChatterFeedConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ChatterFeedConfiguration"
                                 (SalesforceChatterFeedConfigurationProperty -> (Key, Value))
-> Maybe SalesforceChatterFeedConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceChatterFeedConfigurationProperty
chatterFeedConfiguration,
                               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CrawlAttachments" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
crawlAttachments,
                               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ExcludeAttachmentFilePatterns"
                                 (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
excludeAttachmentFilePatterns,
                               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeAttachmentFilePatterns"
                                 (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
includeAttachmentFilePatterns,
                               Key
-> SalesforceKnowledgeArticleConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KnowledgeArticleConfiguration"
                                 (SalesforceKnowledgeArticleConfigurationProperty -> (Key, Value))
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceKnowledgeArticleConfigurationProperty
knowledgeArticleConfiguration,
                               Key
-> SalesforceStandardObjectAttachmentConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardObjectAttachmentConfiguration"
                                 (SalesforceStandardObjectAttachmentConfigurationProperty
 -> (Key, Value))
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectAttachmentConfiguration,
                               Key
-> [SalesforceStandardObjectConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardObjectConfigurations"
                                 ([SalesforceStandardObjectConfigurationProperty] -> (Key, Value))
-> Maybe [SalesforceStandardObjectConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SalesforceStandardObjectConfigurationProperty]
standardObjectConfigurations]))}
instance JSON.ToJSON SalesforceConfigurationProperty where
  toJSON :: SalesforceConfigurationProperty -> Value
toJSON SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
              [Key
"SecretArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
secretArn, Key
"ServerUrl" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
serverUrl]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> SalesforceChatterFeedConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ChatterFeedConfiguration"
                    (SalesforceChatterFeedConfigurationProperty -> (Key, Value))
-> Maybe SalesforceChatterFeedConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceChatterFeedConfigurationProperty
chatterFeedConfiguration,
                  Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CrawlAttachments" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
crawlAttachments,
                  Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ExcludeAttachmentFilePatterns"
                    (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
excludeAttachmentFilePatterns,
                  Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeAttachmentFilePatterns"
                    (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
includeAttachmentFilePatterns,
                  Key
-> SalesforceKnowledgeArticleConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KnowledgeArticleConfiguration"
                    (SalesforceKnowledgeArticleConfigurationProperty -> (Key, Value))
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceKnowledgeArticleConfigurationProperty
knowledgeArticleConfiguration,
                  Key
-> SalesforceStandardObjectAttachmentConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardObjectAttachmentConfiguration"
                    (SalesforceStandardObjectAttachmentConfigurationProperty
 -> (Key, Value))
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectAttachmentConfiguration,
                  Key
-> [SalesforceStandardObjectConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardObjectConfigurations"
                    ([SalesforceStandardObjectConfigurationProperty] -> (Key, Value))
-> Maybe [SalesforceStandardObjectConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SalesforceStandardObjectConfigurationProperty]
standardObjectConfigurations])))
instance Property "ChatterFeedConfiguration" SalesforceConfigurationProperty where
  type PropertyType "ChatterFeedConfiguration" SalesforceConfigurationProperty = SalesforceChatterFeedConfigurationProperty
  set :: PropertyType
  "ChatterFeedConfiguration" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "ChatterFeedConfiguration" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
chatterFeedConfiguration = SalesforceChatterFeedConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ChatterFeedConfiguration" SalesforceConfigurationProperty
SalesforceChatterFeedConfigurationProperty
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "CrawlAttachments" SalesforceConfigurationProperty where
  type PropertyType "CrawlAttachments" SalesforceConfigurationProperty = Value Prelude.Bool
  set :: PropertyType "CrawlAttachments" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType "CrawlAttachments" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {crawlAttachments :: Maybe (Value Bool)
crawlAttachments = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CrawlAttachments" SalesforceConfigurationProperty
Value Bool
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "ExcludeAttachmentFilePatterns" SalesforceConfigurationProperty where
  type PropertyType "ExcludeAttachmentFilePatterns" SalesforceConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType
  "ExcludeAttachmentFilePatterns" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "ExcludeAttachmentFilePatterns" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {excludeAttachmentFilePatterns :: Maybe (ValueList Text)
excludeAttachmentFilePatterns = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ExcludeAttachmentFilePatterns" SalesforceConfigurationProperty
ValueList Text
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "IncludeAttachmentFilePatterns" SalesforceConfigurationProperty where
  type PropertyType "IncludeAttachmentFilePatterns" SalesforceConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType
  "IncludeAttachmentFilePatterns" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "IncludeAttachmentFilePatterns" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {includeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "IncludeAttachmentFilePatterns" SalesforceConfigurationProperty
ValueList Text
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "KnowledgeArticleConfiguration" SalesforceConfigurationProperty where
  type PropertyType "KnowledgeArticleConfiguration" SalesforceConfigurationProperty = SalesforceKnowledgeArticleConfigurationProperty
  set :: PropertyType
  "KnowledgeArticleConfiguration" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "KnowledgeArticleConfiguration" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
knowledgeArticleConfiguration = SalesforceKnowledgeArticleConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "KnowledgeArticleConfiguration" SalesforceConfigurationProperty
SalesforceKnowledgeArticleConfigurationProperty
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "SecretArn" SalesforceConfigurationProperty where
  type PropertyType "SecretArn" SalesforceConfigurationProperty = Value Prelude.Text
  set :: PropertyType "SecretArn" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType "SecretArn" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty {secretArn :: Value Text
secretArn = PropertyType "SecretArn" SalesforceConfigurationProperty
Value Text
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "ServerUrl" SalesforceConfigurationProperty where
  type PropertyType "ServerUrl" SalesforceConfigurationProperty = Value Prelude.Text
  set :: PropertyType "ServerUrl" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType "ServerUrl" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty {serverUrl :: Value Text
serverUrl = PropertyType "ServerUrl" SalesforceConfigurationProperty
Value Text
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "StandardObjectAttachmentConfiguration" SalesforceConfigurationProperty where
  type PropertyType "StandardObjectAttachmentConfiguration" SalesforceConfigurationProperty = SalesforceStandardObjectAttachmentConfigurationProperty
  set :: PropertyType
  "StandardObjectAttachmentConfiguration"
  SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "StandardObjectAttachmentConfiguration"
  SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectAttachmentConfiguration = SalesforceStandardObjectAttachmentConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "StandardObjectAttachmentConfiguration"
  SalesforceConfigurationProperty
SalesforceStandardObjectAttachmentConfigurationProperty
newValue, Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
instance Property "StandardObjectConfigurations" SalesforceConfigurationProperty where
  type PropertyType "StandardObjectConfigurations" SalesforceConfigurationProperty = [SalesforceStandardObjectConfigurationProperty]
  set :: PropertyType
  "StandardObjectConfigurations" SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
-> SalesforceConfigurationProperty
set PropertyType
  "StandardObjectConfigurations" SalesforceConfigurationProperty
newValue SalesforceConfigurationProperty {Maybe [SalesforceStandardObjectConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: SalesforceConfigurationProperty -> ()
chatterFeedConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: SalesforceConfigurationProperty -> Maybe (Value Bool)
excludeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
includeAttachmentFilePatterns :: SalesforceConfigurationProperty -> Maybe (ValueList Text)
knowledgeArticleConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: SalesforceConfigurationProperty -> Value Text
serverUrl :: SalesforceConfigurationProperty -> Value Text
standardObjectAttachmentConfiguration :: SalesforceConfigurationProperty
-> Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: SalesforceConfigurationProperty
-> Maybe [SalesforceStandardObjectConfigurationProperty]
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
..}
    = SalesforceConfigurationProperty
        {standardObjectConfigurations :: Maybe [SalesforceStandardObjectConfigurationProperty]
standardObjectConfigurations = [SalesforceStandardObjectConfigurationProperty]
-> Maybe [SalesforceStandardObjectConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SalesforceStandardObjectConfigurationProperty]
PropertyType
  "StandardObjectConfigurations" SalesforceConfigurationProperty
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe SalesforceChatterFeedConfigurationProperty
Maybe SalesforceKnowledgeArticleConfigurationProperty
Maybe SalesforceStandardObjectAttachmentConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
haddock_workaround_ :: ()
chatterFeedConfiguration :: Maybe SalesforceChatterFeedConfigurationProperty
crawlAttachments :: Maybe (Value Bool)
excludeAttachmentFilePatterns :: Maybe (ValueList Text)
includeAttachmentFilePatterns :: Maybe (ValueList Text)
knowledgeArticleConfiguration :: Maybe SalesforceKnowledgeArticleConfigurationProperty
secretArn :: Value Text
serverUrl :: Value Text
standardObjectAttachmentConfiguration :: Maybe SalesforceStandardObjectAttachmentConfigurationProperty
..}