module Stratosphere.KinesisFirehose.DeliveryStream.SnowflakeDestinationConfigurationProperty (
        module Exports, SnowflakeDestinationConfigurationProperty(..),
        mkSnowflakeDestinationConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.CloudWatchLoggingOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.ProcessingConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.S3DestinationConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.SecretsManagerConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.SnowflakeBufferingHintsProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.SnowflakeRetryOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.SnowflakeRoleConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisFirehose.DeliveryStream.SnowflakeVpcConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SnowflakeDestinationConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html>
    SnowflakeDestinationConfigurationProperty {SnowflakeDestinationConfigurationProperty -> ()
haddock_workaround_ :: (),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-accounturl>
                                               SnowflakeDestinationConfigurationProperty -> Value Text
accountUrl :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-bufferinghints>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
bufferingHints :: (Prelude.Maybe SnowflakeBufferingHintsProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-cloudwatchloggingoptions>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
cloudWatchLoggingOptions :: (Prelude.Maybe CloudWatchLoggingOptionsProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-contentcolumnname>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
contentColumnName :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-dataloadingoption>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-database>
                                               SnowflakeDestinationConfigurationProperty -> Value Text
database :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-keypassphrase>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
keyPassphrase :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-metadatacolumnname>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-privatekey>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-processingconfiguration>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
processingConfiguration :: (Prelude.Maybe ProcessingConfigurationProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-retryoptions>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
retryOptions :: (Prelude.Maybe SnowflakeRetryOptionsProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-rolearn>
                                               SnowflakeDestinationConfigurationProperty -> Value Text
roleARN :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-s3backupmode>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3BackupMode :: (Prelude.Maybe (Value Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-s3configuration>
                                               SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
s3Configuration :: S3DestinationConfigurationProperty,
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-schema>
                                               SnowflakeDestinationConfigurationProperty -> Value Text
schema :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-secretsmanagerconfiguration>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
secretsManagerConfiguration :: (Prelude.Maybe SecretsManagerConfigurationProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-snowflakeroleconfiguration>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeRoleConfiguration :: (Prelude.Maybe SnowflakeRoleConfigurationProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-snowflakevpcconfiguration>
                                               SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
snowflakeVpcConfiguration :: (Prelude.Maybe SnowflakeVpcConfigurationProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-table>
                                               SnowflakeDestinationConfigurationProperty -> Value Text
table :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisfirehose-deliverystream-snowflakedestinationconfiguration.html#cfn-kinesisfirehose-deliverystream-snowflakedestinationconfiguration-user>
                                               SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
user :: (Prelude.Maybe (Value Prelude.Text))}
  deriving stock (SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty -> Bool
(SnowflakeDestinationConfigurationProperty
 -> SnowflakeDestinationConfigurationProperty -> Bool)
-> (SnowflakeDestinationConfigurationProperty
    -> SnowflakeDestinationConfigurationProperty -> Bool)
-> Eq SnowflakeDestinationConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty -> Bool
== :: SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty -> Bool
$c/= :: SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty -> Bool
/= :: SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty -> Bool
Prelude.Eq, Int -> SnowflakeDestinationConfigurationProperty -> ShowS
[SnowflakeDestinationConfigurationProperty] -> ShowS
SnowflakeDestinationConfigurationProperty -> String
(Int -> SnowflakeDestinationConfigurationProperty -> ShowS)
-> (SnowflakeDestinationConfigurationProperty -> String)
-> ([SnowflakeDestinationConfigurationProperty] -> ShowS)
-> Show SnowflakeDestinationConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SnowflakeDestinationConfigurationProperty -> ShowS
showsPrec :: Int -> SnowflakeDestinationConfigurationProperty -> ShowS
$cshow :: SnowflakeDestinationConfigurationProperty -> String
show :: SnowflakeDestinationConfigurationProperty -> String
$cshowList :: [SnowflakeDestinationConfigurationProperty] -> ShowS
showList :: [SnowflakeDestinationConfigurationProperty] -> ShowS
Prelude.Show)
mkSnowflakeDestinationConfigurationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text
     -> Value Prelude.Text
        -> S3DestinationConfigurationProperty
           -> Value Prelude.Text
              -> Value Prelude.Text -> SnowflakeDestinationConfigurationProperty
mkSnowflakeDestinationConfigurationProperty :: Value Text
-> Value Text
-> Value Text
-> S3DestinationConfigurationProperty
-> Value Text
-> Value Text
-> SnowflakeDestinationConfigurationProperty
mkSnowflakeDestinationConfigurationProperty
  Value Text
accountUrl
  Value Text
database
  Value Text
roleARN
  S3DestinationConfigurationProperty
s3Configuration
  Value Text
schema
  Value Text
table
  = SnowflakeDestinationConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), accountUrl :: Value Text
accountUrl = Value Text
accountUrl,
       database :: Value Text
database = Value Text
database, roleARN :: Value Text
roleARN = Value Text
roleARN,
       s3Configuration :: S3DestinationConfigurationProperty
s3Configuration = S3DestinationConfigurationProperty
s3Configuration, schema :: Value Text
schema = Value Text
schema, table :: Value Text
table = Value Text
table,
       bufferingHints :: Maybe SnowflakeBufferingHintsProperty
bufferingHints = Maybe SnowflakeBufferingHintsProperty
forall a. Maybe a
Prelude.Nothing,
       cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
cloudWatchLoggingOptions = Maybe CloudWatchLoggingOptionsProperty
forall a. Maybe a
Prelude.Nothing,
       contentColumnName :: Maybe (Value Text)
contentColumnName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       dataLoadingOption :: Maybe (Value Text)
dataLoadingOption = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       keyPassphrase :: Maybe (Value Text)
keyPassphrase = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       metaDataColumnName :: Maybe (Value Text)
metaDataColumnName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, privateKey :: Maybe (Value Text)
privateKey = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       processingConfiguration :: Maybe ProcessingConfigurationProperty
processingConfiguration = Maybe ProcessingConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       retryOptions :: Maybe SnowflakeRetryOptionsProperty
retryOptions = Maybe SnowflakeRetryOptionsProperty
forall a. Maybe a
Prelude.Nothing, s3BackupMode :: Maybe (Value Text)
s3BackupMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
secretsManagerConfiguration = Maybe SecretsManagerConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeRoleConfiguration = Maybe SnowflakeRoleConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
snowflakeVpcConfiguration = Maybe SnowflakeVpcConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       user :: Maybe (Value Text)
user = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SnowflakeDestinationConfigurationProperty where
  toResourceProperties :: SnowflakeDestinationConfigurationProperty -> ResourceProperties
toResourceProperties SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::KinesisFirehose::DeliveryStream.SnowflakeDestinationConfiguration",
         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
"AccountUrl" 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
accountUrl, Key
"Database" 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
database,
                            Key
"RoleARN" 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
roleARN,
                            Key
"S3Configuration" Key -> S3DestinationConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3DestinationConfigurationProperty
s3Configuration, Key
"Schema" 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
schema,
                            Key
"Table" 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
table]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> SnowflakeBufferingHintsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BufferingHints" (SnowflakeBufferingHintsProperty -> (Key, Value))
-> Maybe SnowflakeBufferingHintsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeBufferingHintsProperty
bufferingHints,
                               Key -> CloudWatchLoggingOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CloudWatchLoggingOptions"
                                 (CloudWatchLoggingOptionsProperty -> (Key, Value))
-> Maybe CloudWatchLoggingOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CloudWatchLoggingOptionsProperty
cloudWatchLoggingOptions,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ContentColumnName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
contentColumnName,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DataLoadingOption" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
dataLoadingOption,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KeyPassphrase" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
keyPassphrase,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetaDataColumnName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
metaDataColumnName,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrivateKey" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
privateKey,
                               Key -> ProcessingConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProcessingConfiguration"
                                 (ProcessingConfigurationProperty -> (Key, Value))
-> Maybe ProcessingConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ProcessingConfigurationProperty
processingConfiguration,
                               Key -> SnowflakeRetryOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RetryOptions" (SnowflakeRetryOptionsProperty -> (Key, Value))
-> Maybe SnowflakeRetryOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeRetryOptionsProperty
retryOptions,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"S3BackupMode" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
s3BackupMode,
                               Key -> SecretsManagerConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecretsManagerConfiguration"
                                 (SecretsManagerConfigurationProperty -> (Key, Value))
-> Maybe SecretsManagerConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SecretsManagerConfigurationProperty
secretsManagerConfiguration,
                               Key -> SnowflakeRoleConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnowflakeRoleConfiguration"
                                 (SnowflakeRoleConfigurationProperty -> (Key, Value))
-> Maybe SnowflakeRoleConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeRoleConfigurationProperty
snowflakeRoleConfiguration,
                               Key -> SnowflakeVpcConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnowflakeVpcConfiguration"
                                 (SnowflakeVpcConfigurationProperty -> (Key, Value))
-> Maybe SnowflakeVpcConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeVpcConfigurationProperty
snowflakeVpcConfiguration,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"User" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
user]))}
instance JSON.ToJSON SnowflakeDestinationConfigurationProperty where
  toJSON :: SnowflakeDestinationConfigurationProperty -> Value
toJSON SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = [(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
"AccountUrl" 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
accountUrl, Key
"Database" 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
database,
               Key
"RoleARN" 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
roleARN,
               Key
"S3Configuration" Key -> S3DestinationConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3DestinationConfigurationProperty
s3Configuration, Key
"Schema" 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
schema,
               Key
"Table" 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
table]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> SnowflakeBufferingHintsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BufferingHints" (SnowflakeBufferingHintsProperty -> (Key, Value))
-> Maybe SnowflakeBufferingHintsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeBufferingHintsProperty
bufferingHints,
                  Key -> CloudWatchLoggingOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CloudWatchLoggingOptions"
                    (CloudWatchLoggingOptionsProperty -> (Key, Value))
-> Maybe CloudWatchLoggingOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CloudWatchLoggingOptionsProperty
cloudWatchLoggingOptions,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ContentColumnName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
contentColumnName,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DataLoadingOption" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
dataLoadingOption,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KeyPassphrase" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
keyPassphrase,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetaDataColumnName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
metaDataColumnName,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrivateKey" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
privateKey,
                  Key -> ProcessingConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProcessingConfiguration"
                    (ProcessingConfigurationProperty -> (Key, Value))
-> Maybe ProcessingConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ProcessingConfigurationProperty
processingConfiguration,
                  Key -> SnowflakeRetryOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RetryOptions" (SnowflakeRetryOptionsProperty -> (Key, Value))
-> Maybe SnowflakeRetryOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeRetryOptionsProperty
retryOptions,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"S3BackupMode" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
s3BackupMode,
                  Key -> SecretsManagerConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecretsManagerConfiguration"
                    (SecretsManagerConfigurationProperty -> (Key, Value))
-> Maybe SecretsManagerConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SecretsManagerConfigurationProperty
secretsManagerConfiguration,
                  Key -> SnowflakeRoleConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnowflakeRoleConfiguration"
                    (SnowflakeRoleConfigurationProperty -> (Key, Value))
-> Maybe SnowflakeRoleConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeRoleConfigurationProperty
snowflakeRoleConfiguration,
                  Key -> SnowflakeVpcConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnowflakeVpcConfiguration"
                    (SnowflakeVpcConfigurationProperty -> (Key, Value))
-> Maybe SnowflakeVpcConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnowflakeVpcConfigurationProperty
snowflakeVpcConfiguration,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"User" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
user])))
instance Property "AccountUrl" SnowflakeDestinationConfigurationProperty where
  type PropertyType "AccountUrl" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "AccountUrl" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "AccountUrl" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {accountUrl :: Value Text
accountUrl = PropertyType "AccountUrl" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "BufferingHints" SnowflakeDestinationConfigurationProperty where
  type PropertyType "BufferingHints" SnowflakeDestinationConfigurationProperty = SnowflakeBufferingHintsProperty
  set :: PropertyType
  "BufferingHints" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "BufferingHints" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {bufferingHints :: Maybe SnowflakeBufferingHintsProperty
bufferingHints = SnowflakeBufferingHintsProperty
-> Maybe SnowflakeBufferingHintsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "BufferingHints" SnowflakeDestinationConfigurationProperty
SnowflakeBufferingHintsProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "CloudWatchLoggingOptions" SnowflakeDestinationConfigurationProperty where
  type PropertyType "CloudWatchLoggingOptions" SnowflakeDestinationConfigurationProperty = CloudWatchLoggingOptionsProperty
  set :: PropertyType
  "CloudWatchLoggingOptions"
  SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "CloudWatchLoggingOptions"
  SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
cloudWatchLoggingOptions = CloudWatchLoggingOptionsProperty
-> Maybe CloudWatchLoggingOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "CloudWatchLoggingOptions"
  SnowflakeDestinationConfigurationProperty
CloudWatchLoggingOptionsProperty
newValue, Maybe (Value Text)
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "ContentColumnName" SnowflakeDestinationConfigurationProperty where
  type PropertyType "ContentColumnName" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "ContentColumnName" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "ContentColumnName" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {contentColumnName :: Maybe (Value Text)
contentColumnName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ContentColumnName" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "DataLoadingOption" SnowflakeDestinationConfigurationProperty where
  type PropertyType "DataLoadingOption" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "DataLoadingOption" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "DataLoadingOption" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {dataLoadingOption :: Maybe (Value Text)
dataLoadingOption = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "DataLoadingOption" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "Database" SnowflakeDestinationConfigurationProperty where
  type PropertyType "Database" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "Database" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "Database" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {database :: Value Text
database = PropertyType "Database" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "KeyPassphrase" SnowflakeDestinationConfigurationProperty where
  type PropertyType "KeyPassphrase" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "KeyPassphrase" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "KeyPassphrase" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {keyPassphrase :: Maybe (Value Text)
keyPassphrase = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "KeyPassphrase" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "MetaDataColumnName" SnowflakeDestinationConfigurationProperty where
  type PropertyType "MetaDataColumnName" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "MetaDataColumnName" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "MetaDataColumnName" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {metaDataColumnName :: Maybe (Value Text)
metaDataColumnName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "MetaDataColumnName" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "PrivateKey" SnowflakeDestinationConfigurationProperty where
  type PropertyType "PrivateKey" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "PrivateKey" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "PrivateKey" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {privateKey :: Maybe (Value Text)
privateKey = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PrivateKey" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "ProcessingConfiguration" SnowflakeDestinationConfigurationProperty where
  type PropertyType "ProcessingConfiguration" SnowflakeDestinationConfigurationProperty = ProcessingConfigurationProperty
  set :: PropertyType
  "ProcessingConfiguration" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "ProcessingConfiguration" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {processingConfiguration :: Maybe ProcessingConfigurationProperty
processingConfiguration = ProcessingConfigurationProperty
-> Maybe ProcessingConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ProcessingConfiguration" SnowflakeDestinationConfigurationProperty
ProcessingConfigurationProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "RetryOptions" SnowflakeDestinationConfigurationProperty where
  type PropertyType "RetryOptions" SnowflakeDestinationConfigurationProperty = SnowflakeRetryOptionsProperty
  set :: PropertyType
  "RetryOptions" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "RetryOptions" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {retryOptions :: Maybe SnowflakeRetryOptionsProperty
retryOptions = SnowflakeRetryOptionsProperty
-> Maybe SnowflakeRetryOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "RetryOptions" SnowflakeDestinationConfigurationProperty
SnowflakeRetryOptionsProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "RoleARN" SnowflakeDestinationConfigurationProperty where
  type PropertyType "RoleARN" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "RoleARN" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "RoleARN" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {roleARN :: Value Text
roleARN = PropertyType "RoleARN" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "S3BackupMode" SnowflakeDestinationConfigurationProperty where
  type PropertyType "S3BackupMode" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "S3BackupMode" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "S3BackupMode" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {s3BackupMode :: Maybe (Value Text)
s3BackupMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "S3BackupMode" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "S3Configuration" SnowflakeDestinationConfigurationProperty where
  type PropertyType "S3Configuration" SnowflakeDestinationConfigurationProperty = S3DestinationConfigurationProperty
  set :: PropertyType
  "S3Configuration" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "S3Configuration" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {s3Configuration :: S3DestinationConfigurationProperty
s3Configuration = PropertyType
  "S3Configuration" SnowflakeDestinationConfigurationProperty
S3DestinationConfigurationProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "Schema" SnowflakeDestinationConfigurationProperty where
  type PropertyType "Schema" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "Schema" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "Schema" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty {schema :: Value Text
schema = PropertyType "Schema" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "SecretsManagerConfiguration" SnowflakeDestinationConfigurationProperty where
  type PropertyType "SecretsManagerConfiguration" SnowflakeDestinationConfigurationProperty = SecretsManagerConfigurationProperty
  set :: PropertyType
  "SecretsManagerConfiguration"
  SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "SecretsManagerConfiguration"
  SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
secretsManagerConfiguration = SecretsManagerConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "SecretsManagerConfiguration"
  SnowflakeDestinationConfigurationProperty
SecretsManagerConfigurationProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "SnowflakeRoleConfiguration" SnowflakeDestinationConfigurationProperty where
  type PropertyType "SnowflakeRoleConfiguration" SnowflakeDestinationConfigurationProperty = SnowflakeRoleConfigurationProperty
  set :: PropertyType
  "SnowflakeRoleConfiguration"
  SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "SnowflakeRoleConfiguration"
  SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeRoleConfiguration = SnowflakeRoleConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "SnowflakeRoleConfiguration"
  SnowflakeDestinationConfigurationProperty
SnowflakeRoleConfigurationProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "SnowflakeVpcConfiguration" SnowflakeDestinationConfigurationProperty where
  type PropertyType "SnowflakeVpcConfiguration" SnowflakeDestinationConfigurationProperty = SnowflakeVpcConfigurationProperty
  set :: PropertyType
  "SnowflakeVpcConfiguration"
  SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType
  "SnowflakeVpcConfiguration"
  SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
snowflakeVpcConfiguration = SnowflakeVpcConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "SnowflakeVpcConfiguration"
  SnowflakeDestinationConfigurationProperty
SnowflakeVpcConfigurationProperty
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
instance Property "Table" SnowflakeDestinationConfigurationProperty where
  type PropertyType "Table" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "Table" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "Table" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty {table :: Value Text
table = PropertyType "Table" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
user :: Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
user :: Maybe (Value Text)
..}
instance Property "User" SnowflakeDestinationConfigurationProperty where
  type PropertyType "User" SnowflakeDestinationConfigurationProperty = Value Prelude.Text
  set :: PropertyType "User" SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
-> SnowflakeDestinationConfigurationProperty
set PropertyType "User" SnowflakeDestinationConfigurationProperty
newValue SnowflakeDestinationConfigurationProperty {Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: SnowflakeDestinationConfigurationProperty -> ()
accountUrl :: SnowflakeDestinationConfigurationProperty -> Value Text
bufferingHints :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
dataLoadingOption :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
database :: SnowflakeDestinationConfigurationProperty -> Value Text
keyPassphrase :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
metaDataColumnName :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
privateKey :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
processingConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe ProcessingConfigurationProperty
retryOptions :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRetryOptionsProperty
roleARN :: SnowflakeDestinationConfigurationProperty -> Value Text
s3BackupMode :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
s3Configuration :: SnowflakeDestinationConfigurationProperty
-> S3DestinationConfigurationProperty
schema :: SnowflakeDestinationConfigurationProperty -> Value Text
secretsManagerConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: SnowflakeDestinationConfigurationProperty
-> Maybe SnowflakeVpcConfigurationProperty
table :: SnowflakeDestinationConfigurationProperty -> Value Text
user :: SnowflakeDestinationConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
user :: Maybe (Value Text)
..}
    = SnowflakeDestinationConfigurationProperty
        {user :: Maybe (Value Text)
user = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "User" SnowflakeDestinationConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe CloudWatchLoggingOptionsProperty
Maybe ProcessingConfigurationProperty
Maybe SecretsManagerConfigurationProperty
Maybe SnowflakeBufferingHintsProperty
Maybe SnowflakeRetryOptionsProperty
Maybe SnowflakeRoleConfigurationProperty
Maybe SnowflakeVpcConfigurationProperty
()
Value Text
S3DestinationConfigurationProperty
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
haddock_workaround_ :: ()
accountUrl :: Value Text
bufferingHints :: Maybe SnowflakeBufferingHintsProperty
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptionsProperty
contentColumnName :: Maybe (Value Text)
dataLoadingOption :: Maybe (Value Text)
database :: Value Text
keyPassphrase :: Maybe (Value Text)
metaDataColumnName :: Maybe (Value Text)
privateKey :: Maybe (Value Text)
processingConfiguration :: Maybe ProcessingConfigurationProperty
retryOptions :: Maybe SnowflakeRetryOptionsProperty
roleARN :: Value Text
s3BackupMode :: Maybe (Value Text)
s3Configuration :: S3DestinationConfigurationProperty
schema :: Value Text
secretsManagerConfiguration :: Maybe SecretsManagerConfigurationProperty
snowflakeRoleConfiguration :: Maybe SnowflakeRoleConfigurationProperty
snowflakeVpcConfiguration :: Maybe SnowflakeVpcConfigurationProperty
table :: Value Text
..}