{-# 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.SplunkDestinationUpdate
-- 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.SplunkDestinationUpdate 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.CloudWatchLoggingOptions
import Amazonka.Firehose.Types.HECEndpointType
import Amazonka.Firehose.Types.ProcessingConfiguration
import Amazonka.Firehose.Types.S3DestinationUpdate
import Amazonka.Firehose.Types.SplunkRetryOptions
import Amazonka.Firehose.Types.SplunkS3BackupMode
import qualified Amazonka.Prelude as Prelude

-- | Describes an update for a destination in Splunk.
--
-- /See:/ 'newSplunkDestinationUpdate' smart constructor.
data SplunkDestinationUpdate = SplunkDestinationUpdate'
  { -- | The Amazon CloudWatch logging options for your delivery stream.
    SplunkDestinationUpdate -> Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions :: Prelude.Maybe CloudWatchLoggingOptions,
    -- | The amount of time that Kinesis Data Firehose waits to receive an
    -- acknowledgment from Splunk after it sends data. At the end of the
    -- timeout period, Kinesis Data Firehose either tries to send the data
    -- again or considers it an error, based on your retry settings.
    SplunkDestinationUpdate -> Maybe Natural
hECAcknowledgmentTimeoutInSeconds :: Prelude.Maybe Prelude.Natural,
    -- | The HTTP Event Collector (HEC) endpoint to which Kinesis Data Firehose
    -- sends your data.
    SplunkDestinationUpdate -> Maybe Text
hECEndpoint :: Prelude.Maybe Prelude.Text,
    -- | This type can be either \"Raw\" or \"Event.\"
    SplunkDestinationUpdate -> Maybe HECEndpointType
hECEndpointType :: Prelude.Maybe HECEndpointType,
    -- | A GUID that you obtain from your Splunk cluster when you create a new
    -- HEC endpoint.
    SplunkDestinationUpdate -> Maybe Text
hECToken :: Prelude.Maybe Prelude.Text,
    -- | The data processing configuration.
    SplunkDestinationUpdate -> Maybe ProcessingConfiguration
processingConfiguration :: Prelude.Maybe ProcessingConfiguration,
    -- | The retry behavior in case Kinesis Data Firehose is unable to deliver
    -- data to Splunk or if it doesn\'t receive an acknowledgment of receipt
    -- from Splunk.
    SplunkDestinationUpdate -> Maybe SplunkRetryOptions
retryOptions :: Prelude.Maybe SplunkRetryOptions,
    -- | Specifies how you want Kinesis Data Firehose to back up documents to
    -- Amazon S3. When set to @FailedDocumentsOnly@, Kinesis Data Firehose
    -- writes any data that could not be indexed to the configured Amazon S3
    -- destination. When set to @AllEvents@, Kinesis Data Firehose delivers all
    -- incoming records to Amazon S3, and also writes failed documents to
    -- Amazon S3. The default value is @FailedEventsOnly@.
    --
    -- You can update this backup mode from @FailedEventsOnly@ to @AllEvents@.
    -- You can\'t update it from @AllEvents@ to @FailedEventsOnly@.
    SplunkDestinationUpdate -> Maybe SplunkS3BackupMode
s3BackupMode :: Prelude.Maybe SplunkS3BackupMode,
    -- | Your update to the configuration of the backup Amazon S3 location.
    SplunkDestinationUpdate -> Maybe S3DestinationUpdate
s3Update :: Prelude.Maybe S3DestinationUpdate
  }
  deriving (SplunkDestinationUpdate -> SplunkDestinationUpdate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SplunkDestinationUpdate -> SplunkDestinationUpdate -> Bool
$c/= :: SplunkDestinationUpdate -> SplunkDestinationUpdate -> Bool
== :: SplunkDestinationUpdate -> SplunkDestinationUpdate -> Bool
$c== :: SplunkDestinationUpdate -> SplunkDestinationUpdate -> Bool
Prelude.Eq, ReadPrec [SplunkDestinationUpdate]
ReadPrec SplunkDestinationUpdate
Int -> ReadS SplunkDestinationUpdate
ReadS [SplunkDestinationUpdate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SplunkDestinationUpdate]
$creadListPrec :: ReadPrec [SplunkDestinationUpdate]
readPrec :: ReadPrec SplunkDestinationUpdate
$creadPrec :: ReadPrec SplunkDestinationUpdate
readList :: ReadS [SplunkDestinationUpdate]
$creadList :: ReadS [SplunkDestinationUpdate]
readsPrec :: Int -> ReadS SplunkDestinationUpdate
$creadsPrec :: Int -> ReadS SplunkDestinationUpdate
Prelude.Read, Int -> SplunkDestinationUpdate -> ShowS
[SplunkDestinationUpdate] -> ShowS
SplunkDestinationUpdate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SplunkDestinationUpdate] -> ShowS
$cshowList :: [SplunkDestinationUpdate] -> ShowS
show :: SplunkDestinationUpdate -> String
$cshow :: SplunkDestinationUpdate -> String
showsPrec :: Int -> SplunkDestinationUpdate -> ShowS
$cshowsPrec :: Int -> SplunkDestinationUpdate -> ShowS
Prelude.Show, forall x. Rep SplunkDestinationUpdate x -> SplunkDestinationUpdate
forall x. SplunkDestinationUpdate -> Rep SplunkDestinationUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SplunkDestinationUpdate x -> SplunkDestinationUpdate
$cfrom :: forall x. SplunkDestinationUpdate -> Rep SplunkDestinationUpdate x
Prelude.Generic)

-- |
-- Create a value of 'SplunkDestinationUpdate' 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:
--
-- 'cloudWatchLoggingOptions', 'splunkDestinationUpdate_cloudWatchLoggingOptions' - The Amazon CloudWatch logging options for your delivery stream.
--
-- 'hECAcknowledgmentTimeoutInSeconds', 'splunkDestinationUpdate_hECAcknowledgmentTimeoutInSeconds' - The amount of time that Kinesis Data Firehose waits to receive an
-- acknowledgment from Splunk after it sends data. At the end of the
-- timeout period, Kinesis Data Firehose either tries to send the data
-- again or considers it an error, based on your retry settings.
--
-- 'hECEndpoint', 'splunkDestinationUpdate_hECEndpoint' - The HTTP Event Collector (HEC) endpoint to which Kinesis Data Firehose
-- sends your data.
--
-- 'hECEndpointType', 'splunkDestinationUpdate_hECEndpointType' - This type can be either \"Raw\" or \"Event.\"
--
-- 'hECToken', 'splunkDestinationUpdate_hECToken' - A GUID that you obtain from your Splunk cluster when you create a new
-- HEC endpoint.
--
-- 'processingConfiguration', 'splunkDestinationUpdate_processingConfiguration' - The data processing configuration.
--
-- 'retryOptions', 'splunkDestinationUpdate_retryOptions' - The retry behavior in case Kinesis Data Firehose is unable to deliver
-- data to Splunk or if it doesn\'t receive an acknowledgment of receipt
-- from Splunk.
--
-- 's3BackupMode', 'splunkDestinationUpdate_s3BackupMode' - Specifies how you want Kinesis Data Firehose to back up documents to
-- Amazon S3. When set to @FailedDocumentsOnly@, Kinesis Data Firehose
-- writes any data that could not be indexed to the configured Amazon S3
-- destination. When set to @AllEvents@, Kinesis Data Firehose delivers all
-- incoming records to Amazon S3, and also writes failed documents to
-- Amazon S3. The default value is @FailedEventsOnly@.
--
-- You can update this backup mode from @FailedEventsOnly@ to @AllEvents@.
-- You can\'t update it from @AllEvents@ to @FailedEventsOnly@.
--
-- 's3Update', 'splunkDestinationUpdate_s3Update' - Your update to the configuration of the backup Amazon S3 location.
newSplunkDestinationUpdate ::
  SplunkDestinationUpdate
newSplunkDestinationUpdate :: SplunkDestinationUpdate
newSplunkDestinationUpdate =
  SplunkDestinationUpdate'
    { $sel:cloudWatchLoggingOptions:SplunkDestinationUpdate' :: Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: Maybe Natural
hECAcknowledgmentTimeoutInSeconds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:hECEndpoint:SplunkDestinationUpdate' :: Maybe Text
hECEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:hECEndpointType:SplunkDestinationUpdate' :: Maybe HECEndpointType
hECEndpointType = forall a. Maybe a
Prelude.Nothing,
      $sel:hECToken:SplunkDestinationUpdate' :: Maybe Text
hECToken = forall a. Maybe a
Prelude.Nothing,
      $sel:processingConfiguration:SplunkDestinationUpdate' :: Maybe ProcessingConfiguration
processingConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:retryOptions:SplunkDestinationUpdate' :: Maybe SplunkRetryOptions
retryOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:s3BackupMode:SplunkDestinationUpdate' :: Maybe SplunkS3BackupMode
s3BackupMode = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Update:SplunkDestinationUpdate' :: Maybe S3DestinationUpdate
s3Update = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The amount of time that Kinesis Data Firehose waits to receive an
-- acknowledgment from Splunk after it sends data. At the end of the
-- timeout period, Kinesis Data Firehose either tries to send the data
-- again or considers it an error, based on your retry settings.
splunkDestinationUpdate_hECAcknowledgmentTimeoutInSeconds :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe Prelude.Natural)
splunkDestinationUpdate_hECAcknowledgmentTimeoutInSeconds :: Lens' SplunkDestinationUpdate (Maybe Natural)
splunkDestinationUpdate_hECAcknowledgmentTimeoutInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe Natural
hECAcknowledgmentTimeoutInSeconds :: Maybe Natural
$sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Natural
hECAcknowledgmentTimeoutInSeconds} -> Maybe Natural
hECAcknowledgmentTimeoutInSeconds) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe Natural
a -> SplunkDestinationUpdate
s {$sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: Maybe Natural
hECAcknowledgmentTimeoutInSeconds = Maybe Natural
a} :: SplunkDestinationUpdate)

-- | The HTTP Event Collector (HEC) endpoint to which Kinesis Data Firehose
-- sends your data.
splunkDestinationUpdate_hECEndpoint :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe Prelude.Text)
splunkDestinationUpdate_hECEndpoint :: Lens' SplunkDestinationUpdate (Maybe Text)
splunkDestinationUpdate_hECEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe Text
hECEndpoint :: Maybe Text
$sel:hECEndpoint:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
hECEndpoint} -> Maybe Text
hECEndpoint) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe Text
a -> SplunkDestinationUpdate
s {$sel:hECEndpoint:SplunkDestinationUpdate' :: Maybe Text
hECEndpoint = Maybe Text
a} :: SplunkDestinationUpdate)

-- | This type can be either \"Raw\" or \"Event.\"
splunkDestinationUpdate_hECEndpointType :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe HECEndpointType)
splunkDestinationUpdate_hECEndpointType :: Lens' SplunkDestinationUpdate (Maybe HECEndpointType)
splunkDestinationUpdate_hECEndpointType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe HECEndpointType
hECEndpointType :: Maybe HECEndpointType
$sel:hECEndpointType:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe HECEndpointType
hECEndpointType} -> Maybe HECEndpointType
hECEndpointType) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe HECEndpointType
a -> SplunkDestinationUpdate
s {$sel:hECEndpointType:SplunkDestinationUpdate' :: Maybe HECEndpointType
hECEndpointType = Maybe HECEndpointType
a} :: SplunkDestinationUpdate)

-- | A GUID that you obtain from your Splunk cluster when you create a new
-- HEC endpoint.
splunkDestinationUpdate_hECToken :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe Prelude.Text)
splunkDestinationUpdate_hECToken :: Lens' SplunkDestinationUpdate (Maybe Text)
splunkDestinationUpdate_hECToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe Text
hECToken :: Maybe Text
$sel:hECToken:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
hECToken} -> Maybe Text
hECToken) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe Text
a -> SplunkDestinationUpdate
s {$sel:hECToken:SplunkDestinationUpdate' :: Maybe Text
hECToken = Maybe Text
a} :: SplunkDestinationUpdate)

-- | The data processing configuration.
splunkDestinationUpdate_processingConfiguration :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe ProcessingConfiguration)
splunkDestinationUpdate_processingConfiguration :: Lens' SplunkDestinationUpdate (Maybe ProcessingConfiguration)
splunkDestinationUpdate_processingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe ProcessingConfiguration
processingConfiguration :: Maybe ProcessingConfiguration
$sel:processingConfiguration:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe ProcessingConfiguration
processingConfiguration} -> Maybe ProcessingConfiguration
processingConfiguration) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe ProcessingConfiguration
a -> SplunkDestinationUpdate
s {$sel:processingConfiguration:SplunkDestinationUpdate' :: Maybe ProcessingConfiguration
processingConfiguration = Maybe ProcessingConfiguration
a} :: SplunkDestinationUpdate)

-- | The retry behavior in case Kinesis Data Firehose is unable to deliver
-- data to Splunk or if it doesn\'t receive an acknowledgment of receipt
-- from Splunk.
splunkDestinationUpdate_retryOptions :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe SplunkRetryOptions)
splunkDestinationUpdate_retryOptions :: Lens' SplunkDestinationUpdate (Maybe SplunkRetryOptions)
splunkDestinationUpdate_retryOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe SplunkRetryOptions
retryOptions :: Maybe SplunkRetryOptions
$sel:retryOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkRetryOptions
retryOptions} -> Maybe SplunkRetryOptions
retryOptions) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe SplunkRetryOptions
a -> SplunkDestinationUpdate
s {$sel:retryOptions:SplunkDestinationUpdate' :: Maybe SplunkRetryOptions
retryOptions = Maybe SplunkRetryOptions
a} :: SplunkDestinationUpdate)

-- | Specifies how you want Kinesis Data Firehose to back up documents to
-- Amazon S3. When set to @FailedDocumentsOnly@, Kinesis Data Firehose
-- writes any data that could not be indexed to the configured Amazon S3
-- destination. When set to @AllEvents@, Kinesis Data Firehose delivers all
-- incoming records to Amazon S3, and also writes failed documents to
-- Amazon S3. The default value is @FailedEventsOnly@.
--
-- You can update this backup mode from @FailedEventsOnly@ to @AllEvents@.
-- You can\'t update it from @AllEvents@ to @FailedEventsOnly@.
splunkDestinationUpdate_s3BackupMode :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe SplunkS3BackupMode)
splunkDestinationUpdate_s3BackupMode :: Lens' SplunkDestinationUpdate (Maybe SplunkS3BackupMode)
splunkDestinationUpdate_s3BackupMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe SplunkS3BackupMode
s3BackupMode :: Maybe SplunkS3BackupMode
$sel:s3BackupMode:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkS3BackupMode
s3BackupMode} -> Maybe SplunkS3BackupMode
s3BackupMode) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe SplunkS3BackupMode
a -> SplunkDestinationUpdate
s {$sel:s3BackupMode:SplunkDestinationUpdate' :: Maybe SplunkS3BackupMode
s3BackupMode = Maybe SplunkS3BackupMode
a} :: SplunkDestinationUpdate)

-- | Your update to the configuration of the backup Amazon S3 location.
splunkDestinationUpdate_s3Update :: Lens.Lens' SplunkDestinationUpdate (Prelude.Maybe S3DestinationUpdate)
splunkDestinationUpdate_s3Update :: Lens' SplunkDestinationUpdate (Maybe S3DestinationUpdate)
splunkDestinationUpdate_s3Update = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplunkDestinationUpdate' {Maybe S3DestinationUpdate
s3Update :: Maybe S3DestinationUpdate
$sel:s3Update:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe S3DestinationUpdate
s3Update} -> Maybe S3DestinationUpdate
s3Update) (\s :: SplunkDestinationUpdate
s@SplunkDestinationUpdate' {} Maybe S3DestinationUpdate
a -> SplunkDestinationUpdate
s {$sel:s3Update:SplunkDestinationUpdate' :: Maybe S3DestinationUpdate
s3Update = Maybe S3DestinationUpdate
a} :: SplunkDestinationUpdate)

instance Prelude.Hashable SplunkDestinationUpdate where
  hashWithSalt :: Int -> SplunkDestinationUpdate -> Int
hashWithSalt Int
_salt SplunkDestinationUpdate' {Maybe Natural
Maybe Text
Maybe CloudWatchLoggingOptions
Maybe HECEndpointType
Maybe ProcessingConfiguration
Maybe S3DestinationUpdate
Maybe SplunkRetryOptions
Maybe SplunkS3BackupMode
s3Update :: Maybe S3DestinationUpdate
s3BackupMode :: Maybe SplunkS3BackupMode
retryOptions :: Maybe SplunkRetryOptions
processingConfiguration :: Maybe ProcessingConfiguration
hECToken :: Maybe Text
hECEndpointType :: Maybe HECEndpointType
hECEndpoint :: Maybe Text
hECAcknowledgmentTimeoutInSeconds :: Maybe Natural
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
$sel:s3Update:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe S3DestinationUpdate
$sel:s3BackupMode:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkS3BackupMode
$sel:retryOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkRetryOptions
$sel:processingConfiguration:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe ProcessingConfiguration
$sel:hECToken:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECEndpointType:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe HECEndpointType
$sel:hECEndpoint:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Natural
$sel:cloudWatchLoggingOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe CloudWatchLoggingOptions
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CloudWatchLoggingOptions
cloudWatchLoggingOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
hECAcknowledgmentTimeoutInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hECEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HECEndpointType
hECEndpointType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hECToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProcessingConfiguration
processingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SplunkRetryOptions
retryOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SplunkS3BackupMode
s3BackupMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3DestinationUpdate
s3Update

instance Prelude.NFData SplunkDestinationUpdate where
  rnf :: SplunkDestinationUpdate -> ()
rnf SplunkDestinationUpdate' {Maybe Natural
Maybe Text
Maybe CloudWatchLoggingOptions
Maybe HECEndpointType
Maybe ProcessingConfiguration
Maybe S3DestinationUpdate
Maybe SplunkRetryOptions
Maybe SplunkS3BackupMode
s3Update :: Maybe S3DestinationUpdate
s3BackupMode :: Maybe SplunkS3BackupMode
retryOptions :: Maybe SplunkRetryOptions
processingConfiguration :: Maybe ProcessingConfiguration
hECToken :: Maybe Text
hECEndpointType :: Maybe HECEndpointType
hECEndpoint :: Maybe Text
hECAcknowledgmentTimeoutInSeconds :: Maybe Natural
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
$sel:s3Update:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe S3DestinationUpdate
$sel:s3BackupMode:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkS3BackupMode
$sel:retryOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkRetryOptions
$sel:processingConfiguration:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe ProcessingConfiguration
$sel:hECToken:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECEndpointType:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe HECEndpointType
$sel:hECEndpoint:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Natural
$sel:cloudWatchLoggingOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe CloudWatchLoggingOptions
..} =
    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 Natural
hECAcknowledgmentTimeoutInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hECEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HECEndpointType
hECEndpointType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hECToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProcessingConfiguration
processingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SplunkRetryOptions
retryOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SplunkS3BackupMode
s3BackupMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3DestinationUpdate
s3Update

instance Data.ToJSON SplunkDestinationUpdate where
  toJSON :: SplunkDestinationUpdate -> Value
toJSON SplunkDestinationUpdate' {Maybe Natural
Maybe Text
Maybe CloudWatchLoggingOptions
Maybe HECEndpointType
Maybe ProcessingConfiguration
Maybe S3DestinationUpdate
Maybe SplunkRetryOptions
Maybe SplunkS3BackupMode
s3Update :: Maybe S3DestinationUpdate
s3BackupMode :: Maybe SplunkS3BackupMode
retryOptions :: Maybe SplunkRetryOptions
processingConfiguration :: Maybe ProcessingConfiguration
hECToken :: Maybe Text
hECEndpointType :: Maybe HECEndpointType
hECEndpoint :: Maybe Text
hECAcknowledgmentTimeoutInSeconds :: Maybe Natural
cloudWatchLoggingOptions :: Maybe CloudWatchLoggingOptions
$sel:s3Update:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe S3DestinationUpdate
$sel:s3BackupMode:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkS3BackupMode
$sel:retryOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe SplunkRetryOptions
$sel:processingConfiguration:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe ProcessingConfiguration
$sel:hECToken:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECEndpointType:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe HECEndpointType
$sel:hECEndpoint:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Text
$sel:hECAcknowledgmentTimeoutInSeconds:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe Natural
$sel:cloudWatchLoggingOptions:SplunkDestinationUpdate' :: SplunkDestinationUpdate -> Maybe CloudWatchLoggingOptions
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"HECAcknowledgmentTimeoutInSeconds" 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 Natural
hECAcknowledgmentTimeoutInSeconds,
            (Key
"HECEndpoint" 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
hECEndpoint,
            (Key
"HECEndpointType" 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 HECEndpointType
hECEndpointType,
            (Key
"HECToken" 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
hECToken,
            (Key
"ProcessingConfiguration" 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 ProcessingConfiguration
processingConfiguration,
            (Key
"RetryOptions" 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 SplunkRetryOptions
retryOptions,
            (Key
"S3BackupMode" 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 SplunkS3BackupMode
s3BackupMode,
            (Key
"S3Update" 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 S3DestinationUpdate
s3Update
          ]
      )