{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Firehose.Types.S3DestinationConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Firehose.Types.S3DestinationConfiguration where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Firehose.Types.BufferingHints
import Amazonka.Firehose.Types.CloudWatchLoggingOptions
import Amazonka.Firehose.Types.CompressionFormat
import Amazonka.Firehose.Types.EncryptionConfiguration
import qualified Amazonka.Prelude as Prelude

-- | Describes the configuration of a destination in Amazon S3.
--
-- /See:/ 'newS3DestinationConfiguration' smart constructor.
data S3DestinationConfiguration = S3DestinationConfiguration'
  { -- | The buffering option. If no value is specified, @BufferingHints@ object
    -- default values are used.
    S3DestinationConfiguration -> Maybe BufferingHints
bufferingHints :: Prelude.Maybe BufferingHints,
    -- | The CloudWatch logging options for your delivery stream.
    S3DestinationConfiguration -> Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions :: Prelude.Maybe CloudWatchLoggingOptions,
    -- | The compression format. If no value is specified, the default is
    -- @UNCOMPRESSED@.
    --
    -- The compression formats @SNAPPY@ or @ZIP@ cannot be specified for Amazon
    -- Redshift destinations because they are not supported by the Amazon
    -- Redshift @COPY@ operation that reads from the S3 bucket.
    S3DestinationConfiguration -> Maybe CompressionFormat
compressionFormat :: Prelude.Maybe CompressionFormat,
    -- | The encryption configuration. If no value is specified, the default is
    -- no encryption.
    S3DestinationConfiguration -> Maybe EncryptionConfiguration
encryptionConfiguration :: Prelude.Maybe EncryptionConfiguration,
    -- | A prefix that Kinesis Data Firehose evaluates and adds to failed records
    -- before writing them to S3. This prefix appears immediately following the
    -- bucket name. For information about how to specify this prefix, see
    -- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
    S3DestinationConfiguration -> Maybe Text
errorOutputPrefix :: Prelude.Maybe Prelude.Text,
    -- | The \"YYYY\/MM\/DD\/HH\" time format prefix is automatically used for
    -- delivered Amazon S3 files. You can also specify a custom prefix, as
    -- described in
    -- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
    S3DestinationConfiguration -> Maybe Text
prefix :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon Web Services credentials.
    -- For more information, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
    S3DestinationConfiguration -> Text
roleARN :: Prelude.Text,
    -- | The ARN of the S3 bucket. For more information, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
    S3DestinationConfiguration -> Text
bucketARN :: Prelude.Text
  }
  deriving (S3DestinationConfiguration -> S3DestinationConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: S3DestinationConfiguration -> S3DestinationConfiguration -> Bool
$c/= :: S3DestinationConfiguration -> S3DestinationConfiguration -> Bool
== :: S3DestinationConfiguration -> S3DestinationConfiguration -> Bool
$c== :: S3DestinationConfiguration -> S3DestinationConfiguration -> Bool
Prelude.Eq, ReadPrec [S3DestinationConfiguration]
ReadPrec S3DestinationConfiguration
Int -> ReadS S3DestinationConfiguration
ReadS [S3DestinationConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [S3DestinationConfiguration]
$creadListPrec :: ReadPrec [S3DestinationConfiguration]
readPrec :: ReadPrec S3DestinationConfiguration
$creadPrec :: ReadPrec S3DestinationConfiguration
readList :: ReadS [S3DestinationConfiguration]
$creadList :: ReadS [S3DestinationConfiguration]
readsPrec :: Int -> ReadS S3DestinationConfiguration
$creadsPrec :: Int -> ReadS S3DestinationConfiguration
Prelude.Read, Int -> S3DestinationConfiguration -> ShowS
[S3DestinationConfiguration] -> ShowS
S3DestinationConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [S3DestinationConfiguration] -> ShowS
$cshowList :: [S3DestinationConfiguration] -> ShowS
show :: S3DestinationConfiguration -> String
$cshow :: S3DestinationConfiguration -> String
showsPrec :: Int -> S3DestinationConfiguration -> ShowS
$cshowsPrec :: Int -> S3DestinationConfiguration -> ShowS
Prelude.Show, forall x.
Rep S3DestinationConfiguration x -> S3DestinationConfiguration
forall x.
S3DestinationConfiguration -> Rep S3DestinationConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep S3DestinationConfiguration x -> S3DestinationConfiguration
$cfrom :: forall x.
S3DestinationConfiguration -> Rep S3DestinationConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'S3DestinationConfiguration' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'bufferingHints', 's3DestinationConfiguration_bufferingHints' - The buffering option. If no value is specified, @BufferingHints@ object
-- default values are used.
--
-- 'cloudWatchLoggingOptions', 's3DestinationConfiguration_cloudWatchLoggingOptions' - The CloudWatch logging options for your delivery stream.
--
-- 'compressionFormat', 's3DestinationConfiguration_compressionFormat' - The compression format. If no value is specified, the default is
-- @UNCOMPRESSED@.
--
-- The compression formats @SNAPPY@ or @ZIP@ cannot be specified for Amazon
-- Redshift destinations because they are not supported by the Amazon
-- Redshift @COPY@ operation that reads from the S3 bucket.
--
-- 'encryptionConfiguration', 's3DestinationConfiguration_encryptionConfiguration' - The encryption configuration. If no value is specified, the default is
-- no encryption.
--
-- 'errorOutputPrefix', 's3DestinationConfiguration_errorOutputPrefix' - A prefix that Kinesis Data Firehose evaluates and adds to failed records
-- before writing them to S3. This prefix appears immediately following the
-- bucket name. For information about how to specify this prefix, see
-- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
--
-- 'prefix', 's3DestinationConfiguration_prefix' - The \"YYYY\/MM\/DD\/HH\" time format prefix is automatically used for
-- delivered Amazon S3 files. You can also specify a custom prefix, as
-- described in
-- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
--
-- 'roleARN', 's3DestinationConfiguration_roleARN' - The Amazon Resource Name (ARN) of the Amazon Web Services credentials.
-- For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
--
-- 'bucketARN', 's3DestinationConfiguration_bucketARN' - The ARN of the S3 bucket. For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
newS3DestinationConfiguration ::
  -- | 'roleARN'
  Prelude.Text ->
  -- | 'bucketARN'
  Prelude.Text ->
  S3DestinationConfiguration
newS3DestinationConfiguration :: Text -> Text -> S3DestinationConfiguration
newS3DestinationConfiguration Text
pRoleARN_ Text
pBucketARN_ =
  S3DestinationConfiguration'
    { $sel:bufferingHints:S3DestinationConfiguration' :: Maybe BufferingHints
bufferingHints =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:compressionFormat:S3DestinationConfiguration' :: Maybe CompressionFormat
compressionFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionConfiguration:S3DestinationConfiguration' :: Maybe EncryptionConfiguration
encryptionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:errorOutputPrefix:S3DestinationConfiguration' :: Maybe Text
errorOutputPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:prefix:S3DestinationConfiguration' :: Maybe Text
prefix = forall a. Maybe a
Prelude.Nothing,
      $sel:roleARN:S3DestinationConfiguration' :: Text
roleARN = Text
pRoleARN_,
      $sel:bucketARN:S3DestinationConfiguration' :: Text
bucketARN = Text
pBucketARN_
    }

-- | The buffering option. If no value is specified, @BufferingHints@ object
-- default values are used.
s3DestinationConfiguration_bufferingHints :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe BufferingHints)
s3DestinationConfiguration_bufferingHints :: Lens' S3DestinationConfiguration (Maybe BufferingHints)
s3DestinationConfiguration_bufferingHints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe BufferingHints
bufferingHints :: Maybe BufferingHints
$sel:bufferingHints:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe BufferingHints
bufferingHints} -> Maybe BufferingHints
bufferingHints) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe BufferingHints
a -> S3DestinationConfiguration
s {$sel:bufferingHints:S3DestinationConfiguration' :: Maybe BufferingHints
bufferingHints = Maybe BufferingHints
a} :: S3DestinationConfiguration)

-- | The CloudWatch logging options for your delivery stream.
s3DestinationConfiguration_cloudWatchLoggingOptions :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe CloudWatchLoggingOptions)
s3DestinationConfiguration_cloudWatchLoggingOptions :: Lens' S3DestinationConfiguration (Maybe CloudWatchLoggingOptions)
s3DestinationConfiguration_cloudWatchLoggingOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
$sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions} -> Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe CloudWatchLoggingOptions
a -> S3DestinationConfiguration
s {$sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions = Maybe CloudWatchLoggingOptions
a} :: S3DestinationConfiguration)

-- | The compression format. If no value is specified, the default is
-- @UNCOMPRESSED@.
--
-- The compression formats @SNAPPY@ or @ZIP@ cannot be specified for Amazon
-- Redshift destinations because they are not supported by the Amazon
-- Redshift @COPY@ operation that reads from the S3 bucket.
s3DestinationConfiguration_compressionFormat :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe CompressionFormat)
s3DestinationConfiguration_compressionFormat :: Lens' S3DestinationConfiguration (Maybe CompressionFormat)
s3DestinationConfiguration_compressionFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe CompressionFormat
compressionFormat :: Maybe CompressionFormat
$sel:compressionFormat:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CompressionFormat
compressionFormat} -> Maybe CompressionFormat
compressionFormat) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe CompressionFormat
a -> S3DestinationConfiguration
s {$sel:compressionFormat:S3DestinationConfiguration' :: Maybe CompressionFormat
compressionFormat = Maybe CompressionFormat
a} :: S3DestinationConfiguration)

-- | The encryption configuration. If no value is specified, the default is
-- no encryption.
s3DestinationConfiguration_encryptionConfiguration :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe EncryptionConfiguration)
s3DestinationConfiguration_encryptionConfiguration :: Lens' S3DestinationConfiguration (Maybe EncryptionConfiguration)
s3DestinationConfiguration_encryptionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe EncryptionConfiguration
encryptionConfiguration :: Maybe EncryptionConfiguration
$sel:encryptionConfiguration:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe EncryptionConfiguration
encryptionConfiguration} -> Maybe EncryptionConfiguration
encryptionConfiguration) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe EncryptionConfiguration
a -> S3DestinationConfiguration
s {$sel:encryptionConfiguration:S3DestinationConfiguration' :: Maybe EncryptionConfiguration
encryptionConfiguration = Maybe EncryptionConfiguration
a} :: S3DestinationConfiguration)

-- | A prefix that Kinesis Data Firehose evaluates and adds to failed records
-- before writing them to S3. This prefix appears immediately following the
-- bucket name. For information about how to specify this prefix, see
-- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
s3DestinationConfiguration_errorOutputPrefix :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe Prelude.Text)
s3DestinationConfiguration_errorOutputPrefix :: Lens' S3DestinationConfiguration (Maybe Text)
s3DestinationConfiguration_errorOutputPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe Text
errorOutputPrefix :: Maybe Text
$sel:errorOutputPrefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
errorOutputPrefix} -> Maybe Text
errorOutputPrefix) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe Text
a -> S3DestinationConfiguration
s {$sel:errorOutputPrefix:S3DestinationConfiguration' :: Maybe Text
errorOutputPrefix = Maybe Text
a} :: S3DestinationConfiguration)

-- | The \"YYYY\/MM\/DD\/HH\" time format prefix is automatically used for
-- delivered Amazon S3 files. You can also specify a custom prefix, as
-- described in
-- <https://docs.aws.amazon.com/firehose/latest/dev/s3-prefixes.html Custom Prefixes for Amazon S3 Objects>.
s3DestinationConfiguration_prefix :: Lens.Lens' S3DestinationConfiguration (Prelude.Maybe Prelude.Text)
s3DestinationConfiguration_prefix :: Lens' S3DestinationConfiguration (Maybe Text)
s3DestinationConfiguration_prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Maybe Text
prefix :: Maybe Text
$sel:prefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
prefix} -> Maybe Text
prefix) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Maybe Text
a -> S3DestinationConfiguration
s {$sel:prefix:S3DestinationConfiguration' :: Maybe Text
prefix = Maybe Text
a} :: S3DestinationConfiguration)

-- | The Amazon Resource Name (ARN) of the Amazon Web Services credentials.
-- For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
s3DestinationConfiguration_roleARN :: Lens.Lens' S3DestinationConfiguration Prelude.Text
s3DestinationConfiguration_roleARN :: Lens' S3DestinationConfiguration Text
s3DestinationConfiguration_roleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Text
roleARN :: Text
$sel:roleARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
roleARN} -> Text
roleARN) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Text
a -> S3DestinationConfiguration
s {$sel:roleARN:S3DestinationConfiguration' :: Text
roleARN = Text
a} :: S3DestinationConfiguration)

-- | The ARN of the S3 bucket. For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
s3DestinationConfiguration_bucketARN :: Lens.Lens' S3DestinationConfiguration Prelude.Text
s3DestinationConfiguration_bucketARN :: Lens' S3DestinationConfiguration Text
s3DestinationConfiguration_bucketARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\S3DestinationConfiguration' {Text
bucketARN :: Text
$sel:bucketARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
bucketARN} -> Text
bucketARN) (\s :: S3DestinationConfiguration
s@S3DestinationConfiguration' {} Text
a -> S3DestinationConfiguration
s {$sel:bucketARN:S3DestinationConfiguration' :: Text
bucketARN = Text
a} :: S3DestinationConfiguration)

instance Prelude.Hashable S3DestinationConfiguration where
  hashWithSalt :: Int -> S3DestinationConfiguration -> Int
hashWithSalt Int
_salt S3DestinationConfiguration' {Maybe Text
Maybe BufferingHints
Maybe CloudWatchLoggingOptions
Maybe CompressionFormat
Maybe EncryptionConfiguration
Text
bucketARN :: Text
roleARN :: Text
prefix :: Maybe Text
errorOutputPrefix :: Maybe Text
encryptionConfiguration :: Maybe EncryptionConfiguration
compressionFormat :: Maybe CompressionFormat
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
bufferingHints :: Maybe BufferingHints
$sel:bucketARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:roleARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:prefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:errorOutputPrefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:encryptionConfiguration:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe EncryptionConfiguration
$sel:compressionFormat:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CompressionFormat
$sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CloudWatchLoggingOptions
$sel:bufferingHints:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe BufferingHints
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BufferingHints
bufferingHints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CompressionFormat
compressionFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionConfiguration
encryptionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
errorOutputPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
bucketARN

instance Prelude.NFData S3DestinationConfiguration where
  rnf :: S3DestinationConfiguration -> ()
rnf S3DestinationConfiguration' {Maybe Text
Maybe BufferingHints
Maybe CloudWatchLoggingOptions
Maybe CompressionFormat
Maybe EncryptionConfiguration
Text
bucketARN :: Text
roleARN :: Text
prefix :: Maybe Text
errorOutputPrefix :: Maybe Text
encryptionConfiguration :: Maybe EncryptionConfiguration
compressionFormat :: Maybe CompressionFormat
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
bufferingHints :: Maybe BufferingHints
$sel:bucketARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:roleARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:prefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:errorOutputPrefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:encryptionConfiguration:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe EncryptionConfiguration
$sel:compressionFormat:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CompressionFormat
$sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CloudWatchLoggingOptions
$sel:bufferingHints:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe BufferingHints
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BufferingHints
bufferingHints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CompressionFormat
compressionFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionConfiguration
encryptionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorOutputPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
prefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
bucketARN

instance Data.ToJSON S3DestinationConfiguration where
  toJSON :: S3DestinationConfiguration -> Value
toJSON S3DestinationConfiguration' {Maybe Text
Maybe BufferingHints
Maybe CloudWatchLoggingOptions
Maybe CompressionFormat
Maybe EncryptionConfiguration
Text
bucketARN :: Text
roleARN :: Text
prefix :: Maybe Text
errorOutputPrefix :: Maybe Text
encryptionConfiguration :: Maybe EncryptionConfiguration
compressionFormat :: Maybe CompressionFormat
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
bufferingHints :: Maybe BufferingHints
$sel:bucketARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:roleARN:S3DestinationConfiguration' :: S3DestinationConfiguration -> Text
$sel:prefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:errorOutputPrefix:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe Text
$sel:encryptionConfiguration:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe EncryptionConfiguration
$sel:compressionFormat:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CompressionFormat
$sel:cloudWatchLoggingOptions:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe CloudWatchLoggingOptions
$sel:bufferingHints:S3DestinationConfiguration' :: S3DestinationConfiguration -> Maybe BufferingHints
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BufferingHints" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe BufferingHints
bufferingHints,
            (Key
"CloudWatchLoggingOptions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions,
            (Key
"CompressionFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CompressionFormat
compressionFormat,
            (Key
"EncryptionConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EncryptionConfiguration
encryptionConfiguration,
            (Key
"ErrorOutputPrefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
errorOutputPrefix,
            (Key
"Prefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
prefix,
            forall a. a -> Maybe a
Prelude.Just (Key
"RoleARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleARN),
            forall a. a -> Maybe a
Prelude.Just (Key
"BucketARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
bucketARN)
          ]
      )