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

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

-- |
-- Module      : Amazonka.Lambda.CreateEventSourceMapping
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a mapping between an event source and an Lambda function. Lambda
-- reads items from the event source and invokes the function.
--
-- For details about how to configure different event sources, see the
-- following topics.
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-ddb.html#services-dynamodb-eventsourcemapping Amazon DynamoDB Streams>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-kinesis.html#services-kinesis-eventsourcemapping Amazon Kinesis>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-sqs.html#events-sqs-eventsource Amazon SQS>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-mq.html#services-mq-eventsourcemapping Amazon MQ and RabbitMQ>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-msk.html Amazon MSK>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/kafka-smaa.html Apache Kafka>
--
-- The following error handling options are available only for stream
-- sources (DynamoDB and Kinesis):
--
-- -   @BisectBatchOnFunctionError@ - If the function returns an error,
--     split the batch in two and retry.
--
-- -   @DestinationConfig@ - Send discarded records to an Amazon SQS queue
--     or Amazon SNS topic.
--
-- -   @MaximumRecordAgeInSeconds@ - Discard records older than the
--     specified age. The default value is infinite (-1). When set to
--     infinite (-1), failed records are retried until the record expires
--
-- -   @MaximumRetryAttempts@ - Discard records after the specified number
--     of retries. The default value is infinite (-1). When set to infinite
--     (-1), failed records are retried until the record expires.
--
-- -   @ParallelizationFactor@ - Process multiple batches from each shard
--     concurrently.
--
-- For information about which configuration parameters apply to each event
-- source, see the following topics.
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-ddb.html#services-ddb-params Amazon DynamoDB Streams>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-kinesis.html#services-kinesis-params Amazon Kinesis>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-sqs.html#services-sqs-params Amazon SQS>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-mq.html#services-mq-params Amazon MQ and RabbitMQ>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-msk.html#services-msk-parms Amazon MSK>
--
-- -   <https://docs.aws.amazon.com/lambda/latest/dg/with-kafka.html#services-kafka-parms Apache Kafka>
module Amazonka.Lambda.CreateEventSourceMapping
  ( -- * Creating a Request
    CreateEventSourceMapping (..),
    newCreateEventSourceMapping,

    -- * Request Lenses
    createEventSourceMapping_amazonManagedKafkaEventSourceConfig,
    createEventSourceMapping_batchSize,
    createEventSourceMapping_bisectBatchOnFunctionError,
    createEventSourceMapping_destinationConfig,
    createEventSourceMapping_enabled,
    createEventSourceMapping_eventSourceArn,
    createEventSourceMapping_filterCriteria,
    createEventSourceMapping_functionResponseTypes,
    createEventSourceMapping_maximumBatchingWindowInSeconds,
    createEventSourceMapping_maximumRecordAgeInSeconds,
    createEventSourceMapping_maximumRetryAttempts,
    createEventSourceMapping_parallelizationFactor,
    createEventSourceMapping_queues,
    createEventSourceMapping_selfManagedEventSource,
    createEventSourceMapping_selfManagedKafkaEventSourceConfig,
    createEventSourceMapping_sourceAccessConfigurations,
    createEventSourceMapping_startingPosition,
    createEventSourceMapping_startingPositionTimestamp,
    createEventSourceMapping_topics,
    createEventSourceMapping_tumblingWindowInSeconds,
    createEventSourceMapping_functionName,

    -- * Destructuring the Response
    EventSourceMappingConfiguration (..),
    newEventSourceMappingConfiguration,

    -- * Response Lenses
    eventSourceMappingConfiguration_amazonManagedKafkaEventSourceConfig,
    eventSourceMappingConfiguration_batchSize,
    eventSourceMappingConfiguration_bisectBatchOnFunctionError,
    eventSourceMappingConfiguration_destinationConfig,
    eventSourceMappingConfiguration_eventSourceArn,
    eventSourceMappingConfiguration_filterCriteria,
    eventSourceMappingConfiguration_functionArn,
    eventSourceMappingConfiguration_functionResponseTypes,
    eventSourceMappingConfiguration_lastModified,
    eventSourceMappingConfiguration_lastProcessingResult,
    eventSourceMappingConfiguration_maximumBatchingWindowInSeconds,
    eventSourceMappingConfiguration_maximumRecordAgeInSeconds,
    eventSourceMappingConfiguration_maximumRetryAttempts,
    eventSourceMappingConfiguration_parallelizationFactor,
    eventSourceMappingConfiguration_queues,
    eventSourceMappingConfiguration_selfManagedEventSource,
    eventSourceMappingConfiguration_selfManagedKafkaEventSourceConfig,
    eventSourceMappingConfiguration_sourceAccessConfigurations,
    eventSourceMappingConfiguration_startingPosition,
    eventSourceMappingConfiguration_startingPositionTimestamp,
    eventSourceMappingConfiguration_state,
    eventSourceMappingConfiguration_stateTransitionReason,
    eventSourceMappingConfiguration_topics,
    eventSourceMappingConfiguration_tumblingWindowInSeconds,
    eventSourceMappingConfiguration_uuid,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Lambda.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateEventSourceMapping' smart constructor.
data CreateEventSourceMapping = CreateEventSourceMapping'
  { -- | Specific configuration settings for an Amazon Managed Streaming for
    -- Apache Kafka (Amazon MSK) event source.
    CreateEventSourceMapping
-> Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig :: Prelude.Maybe AmazonManagedKafkaEventSourceConfig,
    -- | The maximum number of records in each batch that Lambda pulls from your
    -- stream or queue and sends to your function. Lambda passes all of the
    -- records in the batch to the function in a single call, up to the payload
    -- limit for synchronous invocation (6 MB).
    --
    -- -   __Amazon Kinesis__ - Default 100. Max 10,000.
    --
    -- -   __Amazon DynamoDB Streams__ - Default 100. Max 10,000.
    --
    -- -   __Amazon Simple Queue Service__ - Default 10. For standard queues
    --     the max is 10,000. For FIFO queues the max is 10.
    --
    -- -   __Amazon Managed Streaming for Apache Kafka__ - Default 100. Max
    --     10,000.
    --
    -- -   __Self-managed Apache Kafka__ - Default 100. Max 10,000.
    --
    -- -   __Amazon MQ (ActiveMQ and RabbitMQ)__ - Default 100. Max 10,000.
    CreateEventSourceMapping -> Maybe Natural
batchSize :: Prelude.Maybe Prelude.Natural,
    -- | (Streams only) If the function returns an error, split the batch in two
    -- and retry.
    CreateEventSourceMapping -> Maybe Bool
bisectBatchOnFunctionError :: Prelude.Maybe Prelude.Bool,
    -- | (Streams only) An Amazon SQS queue or Amazon SNS topic destination for
    -- discarded records.
    CreateEventSourceMapping -> Maybe DestinationConfig
destinationConfig :: Prelude.Maybe DestinationConfig,
    -- | When true, the event source mapping is active. When false, Lambda pauses
    -- polling and invocation.
    --
    -- Default: True
    CreateEventSourceMapping -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the event source.
    --
    -- -   __Amazon Kinesis__ - The ARN of the data stream or a stream
    --     consumer.
    --
    -- -   __Amazon DynamoDB Streams__ - The ARN of the stream.
    --
    -- -   __Amazon Simple Queue Service__ - The ARN of the queue.
    --
    -- -   __Amazon Managed Streaming for Apache Kafka__ - The ARN of the
    --     cluster.
    --
    -- -   __Amazon MQ__ - The ARN of the broker.
    CreateEventSourceMapping -> Maybe Text
eventSourceArn :: Prelude.Maybe Prelude.Text,
    -- | An object that defines the filter criteria that determine whether Lambda
    -- should process an event. For more information, see
    -- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-eventfiltering.html Lambda event filtering>.
    CreateEventSourceMapping -> Maybe FilterCriteria
filterCriteria :: Prelude.Maybe FilterCriteria,
    -- | (Streams and Amazon SQS) A list of current response type enums applied
    -- to the event source mapping.
    CreateEventSourceMapping -> Maybe [FunctionResponseType]
functionResponseTypes :: Prelude.Maybe [FunctionResponseType],
    -- | The maximum amount of time, in seconds, that Lambda spends gathering
    -- records before invoking the function. You can configure
    -- @MaximumBatchingWindowInSeconds@ to any value from 0 seconds to 300
    -- seconds in increments of seconds.
    --
    -- For streams and Amazon SQS event sources, the default batching window is
    -- 0 seconds. For Amazon MSK, Self-managed Apache Kafka, and Amazon MQ
    -- event sources, the default batching window is 500 ms. Note that because
    -- you can only change @MaximumBatchingWindowInSeconds@ in increments of
    -- seconds, you cannot revert back to the 500 ms default batching window
    -- after you have changed it. To restore the default batching window, you
    -- must create a new event source mapping.
    --
    -- Related setting: For streams and Amazon SQS event sources, when you set
    -- @BatchSize@ to a value greater than 10, you must set
    -- @MaximumBatchingWindowInSeconds@ to at least 1.
    CreateEventSourceMapping -> Maybe Natural
maximumBatchingWindowInSeconds :: Prelude.Maybe Prelude.Natural,
    -- | (Streams only) Discard records older than the specified age. The default
    -- value is infinite (-1).
    CreateEventSourceMapping -> Maybe Int
maximumRecordAgeInSeconds :: Prelude.Maybe Prelude.Int,
    -- | (Streams only) Discard records after the specified number of retries.
    -- The default value is infinite (-1). When set to infinite (-1), failed
    -- records are retried until the record expires.
    CreateEventSourceMapping -> Maybe Int
maximumRetryAttempts :: Prelude.Maybe Prelude.Int,
    -- | (Streams only) The number of batches to process from each shard
    -- concurrently.
    CreateEventSourceMapping -> Maybe Natural
parallelizationFactor :: Prelude.Maybe Prelude.Natural,
    -- | (MQ) The name of the Amazon MQ broker destination queue to consume.
    CreateEventSourceMapping -> Maybe (NonEmpty Text)
queues :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The self-managed Apache Kafka cluster to receive records from.
    CreateEventSourceMapping -> Maybe SelfManagedEventSource
selfManagedEventSource :: Prelude.Maybe SelfManagedEventSource,
    -- | Specific configuration settings for a self-managed Apache Kafka event
    -- source.
    CreateEventSourceMapping -> Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig :: Prelude.Maybe SelfManagedKafkaEventSourceConfig,
    -- | An array of authentication protocols or VPC components required to
    -- secure your event source.
    CreateEventSourceMapping -> Maybe [SourceAccessConfiguration]
sourceAccessConfigurations :: Prelude.Maybe [SourceAccessConfiguration],
    -- | The position in a stream from which to start reading. Required for
    -- Amazon Kinesis, Amazon DynamoDB, and Amazon MSK Streams sources.
    -- @AT_TIMESTAMP@ is supported only for Amazon Kinesis streams.
    CreateEventSourceMapping -> Maybe EventSourcePosition
startingPosition :: Prelude.Maybe EventSourcePosition,
    -- | With @StartingPosition@ set to @AT_TIMESTAMP@, the time from which to
    -- start reading.
    CreateEventSourceMapping -> Maybe POSIX
startingPositionTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The name of the Kafka topic.
    CreateEventSourceMapping -> Maybe (NonEmpty Text)
topics :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | (Streams only) The duration in seconds of a processing window. The range
    -- is between 1 second and 900 seconds.
    CreateEventSourceMapping -> Maybe Natural
tumblingWindowInSeconds :: Prelude.Maybe Prelude.Natural,
    -- | The name of the Lambda function.
    --
    -- __Name formats__
    --
    -- -   __Function name__ - @MyFunction@.
    --
    -- -   __Function ARN__ -
    --     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction@.
    --
    -- -   __Version or Alias ARN__ -
    --     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction:PROD@.
    --
    -- -   __Partial ARN__ - @123456789012:function:MyFunction@.
    --
    -- The length constraint applies only to the full ARN. If you specify only
    -- the function name, it\'s limited to 64 characters in length.
    CreateEventSourceMapping -> Text
functionName :: Prelude.Text
  }
  deriving (CreateEventSourceMapping -> CreateEventSourceMapping -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEventSourceMapping -> CreateEventSourceMapping -> Bool
$c/= :: CreateEventSourceMapping -> CreateEventSourceMapping -> Bool
== :: CreateEventSourceMapping -> CreateEventSourceMapping -> Bool
$c== :: CreateEventSourceMapping -> CreateEventSourceMapping -> Bool
Prelude.Eq, ReadPrec [CreateEventSourceMapping]
ReadPrec CreateEventSourceMapping
Int -> ReadS CreateEventSourceMapping
ReadS [CreateEventSourceMapping]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEventSourceMapping]
$creadListPrec :: ReadPrec [CreateEventSourceMapping]
readPrec :: ReadPrec CreateEventSourceMapping
$creadPrec :: ReadPrec CreateEventSourceMapping
readList :: ReadS [CreateEventSourceMapping]
$creadList :: ReadS [CreateEventSourceMapping]
readsPrec :: Int -> ReadS CreateEventSourceMapping
$creadsPrec :: Int -> ReadS CreateEventSourceMapping
Prelude.Read, Int -> CreateEventSourceMapping -> ShowS
[CreateEventSourceMapping] -> ShowS
CreateEventSourceMapping -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEventSourceMapping] -> ShowS
$cshowList :: [CreateEventSourceMapping] -> ShowS
show :: CreateEventSourceMapping -> String
$cshow :: CreateEventSourceMapping -> String
showsPrec :: Int -> CreateEventSourceMapping -> ShowS
$cshowsPrec :: Int -> CreateEventSourceMapping -> ShowS
Prelude.Show, forall x.
Rep CreateEventSourceMapping x -> CreateEventSourceMapping
forall x.
CreateEventSourceMapping -> Rep CreateEventSourceMapping x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateEventSourceMapping x -> CreateEventSourceMapping
$cfrom :: forall x.
CreateEventSourceMapping -> Rep CreateEventSourceMapping x
Prelude.Generic)

-- |
-- Create a value of 'CreateEventSourceMapping' 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:
--
-- 'amazonManagedKafkaEventSourceConfig', 'createEventSourceMapping_amazonManagedKafkaEventSourceConfig' - Specific configuration settings for an Amazon Managed Streaming for
-- Apache Kafka (Amazon MSK) event source.
--
-- 'batchSize', 'createEventSourceMapping_batchSize' - The maximum number of records in each batch that Lambda pulls from your
-- stream or queue and sends to your function. Lambda passes all of the
-- records in the batch to the function in a single call, up to the payload
-- limit for synchronous invocation (6 MB).
--
-- -   __Amazon Kinesis__ - Default 100. Max 10,000.
--
-- -   __Amazon DynamoDB Streams__ - Default 100. Max 10,000.
--
-- -   __Amazon Simple Queue Service__ - Default 10. For standard queues
--     the max is 10,000. For FIFO queues the max is 10.
--
-- -   __Amazon Managed Streaming for Apache Kafka__ - Default 100. Max
--     10,000.
--
-- -   __Self-managed Apache Kafka__ - Default 100. Max 10,000.
--
-- -   __Amazon MQ (ActiveMQ and RabbitMQ)__ - Default 100. Max 10,000.
--
-- 'bisectBatchOnFunctionError', 'createEventSourceMapping_bisectBatchOnFunctionError' - (Streams only) If the function returns an error, split the batch in two
-- and retry.
--
-- 'destinationConfig', 'createEventSourceMapping_destinationConfig' - (Streams only) An Amazon SQS queue or Amazon SNS topic destination for
-- discarded records.
--
-- 'enabled', 'createEventSourceMapping_enabled' - When true, the event source mapping is active. When false, Lambda pauses
-- polling and invocation.
--
-- Default: True
--
-- 'eventSourceArn', 'createEventSourceMapping_eventSourceArn' - The Amazon Resource Name (ARN) of the event source.
--
-- -   __Amazon Kinesis__ - The ARN of the data stream or a stream
--     consumer.
--
-- -   __Amazon DynamoDB Streams__ - The ARN of the stream.
--
-- -   __Amazon Simple Queue Service__ - The ARN of the queue.
--
-- -   __Amazon Managed Streaming for Apache Kafka__ - The ARN of the
--     cluster.
--
-- -   __Amazon MQ__ - The ARN of the broker.
--
-- 'filterCriteria', 'createEventSourceMapping_filterCriteria' - An object that defines the filter criteria that determine whether Lambda
-- should process an event. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-eventfiltering.html Lambda event filtering>.
--
-- 'functionResponseTypes', 'createEventSourceMapping_functionResponseTypes' - (Streams and Amazon SQS) A list of current response type enums applied
-- to the event source mapping.
--
-- 'maximumBatchingWindowInSeconds', 'createEventSourceMapping_maximumBatchingWindowInSeconds' - The maximum amount of time, in seconds, that Lambda spends gathering
-- records before invoking the function. You can configure
-- @MaximumBatchingWindowInSeconds@ to any value from 0 seconds to 300
-- seconds in increments of seconds.
--
-- For streams and Amazon SQS event sources, the default batching window is
-- 0 seconds. For Amazon MSK, Self-managed Apache Kafka, and Amazon MQ
-- event sources, the default batching window is 500 ms. Note that because
-- you can only change @MaximumBatchingWindowInSeconds@ in increments of
-- seconds, you cannot revert back to the 500 ms default batching window
-- after you have changed it. To restore the default batching window, you
-- must create a new event source mapping.
--
-- Related setting: For streams and Amazon SQS event sources, when you set
-- @BatchSize@ to a value greater than 10, you must set
-- @MaximumBatchingWindowInSeconds@ to at least 1.
--
-- 'maximumRecordAgeInSeconds', 'createEventSourceMapping_maximumRecordAgeInSeconds' - (Streams only) Discard records older than the specified age. The default
-- value is infinite (-1).
--
-- 'maximumRetryAttempts', 'createEventSourceMapping_maximumRetryAttempts' - (Streams only) Discard records after the specified number of retries.
-- The default value is infinite (-1). When set to infinite (-1), failed
-- records are retried until the record expires.
--
-- 'parallelizationFactor', 'createEventSourceMapping_parallelizationFactor' - (Streams only) The number of batches to process from each shard
-- concurrently.
--
-- 'queues', 'createEventSourceMapping_queues' - (MQ) The name of the Amazon MQ broker destination queue to consume.
--
-- 'selfManagedEventSource', 'createEventSourceMapping_selfManagedEventSource' - The self-managed Apache Kafka cluster to receive records from.
--
-- 'selfManagedKafkaEventSourceConfig', 'createEventSourceMapping_selfManagedKafkaEventSourceConfig' - Specific configuration settings for a self-managed Apache Kafka event
-- source.
--
-- 'sourceAccessConfigurations', 'createEventSourceMapping_sourceAccessConfigurations' - An array of authentication protocols or VPC components required to
-- secure your event source.
--
-- 'startingPosition', 'createEventSourceMapping_startingPosition' - The position in a stream from which to start reading. Required for
-- Amazon Kinesis, Amazon DynamoDB, and Amazon MSK Streams sources.
-- @AT_TIMESTAMP@ is supported only for Amazon Kinesis streams.
--
-- 'startingPositionTimestamp', 'createEventSourceMapping_startingPositionTimestamp' - With @StartingPosition@ set to @AT_TIMESTAMP@, the time from which to
-- start reading.
--
-- 'topics', 'createEventSourceMapping_topics' - The name of the Kafka topic.
--
-- 'tumblingWindowInSeconds', 'createEventSourceMapping_tumblingWindowInSeconds' - (Streams only) The duration in seconds of a processing window. The range
-- is between 1 second and 900 seconds.
--
-- 'functionName', 'createEventSourceMapping_functionName' - The name of the Lambda function.
--
-- __Name formats__
--
-- -   __Function name__ - @MyFunction@.
--
-- -   __Function ARN__ -
--     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction@.
--
-- -   __Version or Alias ARN__ -
--     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction:PROD@.
--
-- -   __Partial ARN__ - @123456789012:function:MyFunction@.
--
-- The length constraint applies only to the full ARN. If you specify only
-- the function name, it\'s limited to 64 characters in length.
newCreateEventSourceMapping ::
  -- | 'functionName'
  Prelude.Text ->
  CreateEventSourceMapping
newCreateEventSourceMapping :: Text -> CreateEventSourceMapping
newCreateEventSourceMapping Text
pFunctionName_ =
  CreateEventSourceMapping'
    { $sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:batchSize:CreateEventSourceMapping' :: Maybe Natural
batchSize = forall a. Maybe a
Prelude.Nothing,
      $sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: Maybe Bool
bisectBatchOnFunctionError = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationConfig:CreateEventSourceMapping' :: Maybe DestinationConfig
destinationConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:enabled:CreateEventSourceMapping' :: Maybe Bool
enabled = forall a. Maybe a
Prelude.Nothing,
      $sel:eventSourceArn:CreateEventSourceMapping' :: Maybe Text
eventSourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:filterCriteria:CreateEventSourceMapping' :: Maybe FilterCriteria
filterCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:functionResponseTypes:CreateEventSourceMapping' :: Maybe [FunctionResponseType]
functionResponseTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: Maybe Natural
maximumBatchingWindowInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: Maybe Int
maximumRecordAgeInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumRetryAttempts:CreateEventSourceMapping' :: Maybe Int
maximumRetryAttempts = forall a. Maybe a
Prelude.Nothing,
      $sel:parallelizationFactor:CreateEventSourceMapping' :: Maybe Natural
parallelizationFactor = forall a. Maybe a
Prelude.Nothing,
      $sel:queues:CreateEventSourceMapping' :: Maybe (NonEmpty Text)
queues = forall a. Maybe a
Prelude.Nothing,
      $sel:selfManagedEventSource:CreateEventSourceMapping' :: Maybe SelfManagedEventSource
selfManagedEventSource = forall a. Maybe a
Prelude.Nothing,
      $sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sourceAccessConfigurations:CreateEventSourceMapping' :: Maybe [SourceAccessConfiguration]
sourceAccessConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:startingPosition:CreateEventSourceMapping' :: Maybe EventSourcePosition
startingPosition = forall a. Maybe a
Prelude.Nothing,
      $sel:startingPositionTimestamp:CreateEventSourceMapping' :: Maybe POSIX
startingPositionTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:topics:CreateEventSourceMapping' :: Maybe (NonEmpty Text)
topics = forall a. Maybe a
Prelude.Nothing,
      $sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: Maybe Natural
tumblingWindowInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:CreateEventSourceMapping' :: Text
functionName = Text
pFunctionName_
    }

-- | Specific configuration settings for an Amazon Managed Streaming for
-- Apache Kafka (Amazon MSK) event source.
createEventSourceMapping_amazonManagedKafkaEventSourceConfig :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe AmazonManagedKafkaEventSourceConfig)
createEventSourceMapping_amazonManagedKafkaEventSourceConfig :: Lens'
  CreateEventSourceMapping
  (Maybe AmazonManagedKafkaEventSourceConfig)
createEventSourceMapping_amazonManagedKafkaEventSourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig :: Maybe AmazonManagedKafkaEventSourceConfig
$sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping
-> Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig} -> Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe AmazonManagedKafkaEventSourceConfig
a -> CreateEventSourceMapping
s {$sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig = Maybe AmazonManagedKafkaEventSourceConfig
a} :: CreateEventSourceMapping)

-- | The maximum number of records in each batch that Lambda pulls from your
-- stream or queue and sends to your function. Lambda passes all of the
-- records in the batch to the function in a single call, up to the payload
-- limit for synchronous invocation (6 MB).
--
-- -   __Amazon Kinesis__ - Default 100. Max 10,000.
--
-- -   __Amazon DynamoDB Streams__ - Default 100. Max 10,000.
--
-- -   __Amazon Simple Queue Service__ - Default 10. For standard queues
--     the max is 10,000. For FIFO queues the max is 10.
--
-- -   __Amazon Managed Streaming for Apache Kafka__ - Default 100. Max
--     10,000.
--
-- -   __Self-managed Apache Kafka__ - Default 100. Max 10,000.
--
-- -   __Amazon MQ (ActiveMQ and RabbitMQ)__ - Default 100. Max 10,000.
createEventSourceMapping_batchSize :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Natural)
createEventSourceMapping_batchSize :: Lens' CreateEventSourceMapping (Maybe Natural)
createEventSourceMapping_batchSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Natural
batchSize :: Maybe Natural
$sel:batchSize:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
batchSize} -> Maybe Natural
batchSize) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Natural
a -> CreateEventSourceMapping
s {$sel:batchSize:CreateEventSourceMapping' :: Maybe Natural
batchSize = Maybe Natural
a} :: CreateEventSourceMapping)

-- | (Streams only) If the function returns an error, split the batch in two
-- and retry.
createEventSourceMapping_bisectBatchOnFunctionError :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Bool)
createEventSourceMapping_bisectBatchOnFunctionError :: Lens' CreateEventSourceMapping (Maybe Bool)
createEventSourceMapping_bisectBatchOnFunctionError = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Bool
bisectBatchOnFunctionError :: Maybe Bool
$sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
bisectBatchOnFunctionError} -> Maybe Bool
bisectBatchOnFunctionError) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Bool
a -> CreateEventSourceMapping
s {$sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: Maybe Bool
bisectBatchOnFunctionError = Maybe Bool
a} :: CreateEventSourceMapping)

-- | (Streams only) An Amazon SQS queue or Amazon SNS topic destination for
-- discarded records.
createEventSourceMapping_destinationConfig :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe DestinationConfig)
createEventSourceMapping_destinationConfig :: Lens' CreateEventSourceMapping (Maybe DestinationConfig)
createEventSourceMapping_destinationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe DestinationConfig
destinationConfig :: Maybe DestinationConfig
$sel:destinationConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe DestinationConfig
destinationConfig} -> Maybe DestinationConfig
destinationConfig) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe DestinationConfig
a -> CreateEventSourceMapping
s {$sel:destinationConfig:CreateEventSourceMapping' :: Maybe DestinationConfig
destinationConfig = Maybe DestinationConfig
a} :: CreateEventSourceMapping)

-- | When true, the event source mapping is active. When false, Lambda pauses
-- polling and invocation.
--
-- Default: True
createEventSourceMapping_enabled :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Bool)
createEventSourceMapping_enabled :: Lens' CreateEventSourceMapping (Maybe Bool)
createEventSourceMapping_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Bool
a -> CreateEventSourceMapping
s {$sel:enabled:CreateEventSourceMapping' :: Maybe Bool
enabled = Maybe Bool
a} :: CreateEventSourceMapping)

-- | The Amazon Resource Name (ARN) of the event source.
--
-- -   __Amazon Kinesis__ - The ARN of the data stream or a stream
--     consumer.
--
-- -   __Amazon DynamoDB Streams__ - The ARN of the stream.
--
-- -   __Amazon Simple Queue Service__ - The ARN of the queue.
--
-- -   __Amazon Managed Streaming for Apache Kafka__ - The ARN of the
--     cluster.
--
-- -   __Amazon MQ__ - The ARN of the broker.
createEventSourceMapping_eventSourceArn :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Text)
createEventSourceMapping_eventSourceArn :: Lens' CreateEventSourceMapping (Maybe Text)
createEventSourceMapping_eventSourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Text
eventSourceArn :: Maybe Text
$sel:eventSourceArn:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Text
eventSourceArn} -> Maybe Text
eventSourceArn) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Text
a -> CreateEventSourceMapping
s {$sel:eventSourceArn:CreateEventSourceMapping' :: Maybe Text
eventSourceArn = Maybe Text
a} :: CreateEventSourceMapping)

-- | An object that defines the filter criteria that determine whether Lambda
-- should process an event. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-eventfiltering.html Lambda event filtering>.
createEventSourceMapping_filterCriteria :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe FilterCriteria)
createEventSourceMapping_filterCriteria :: Lens' CreateEventSourceMapping (Maybe FilterCriteria)
createEventSourceMapping_filterCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe FilterCriteria
filterCriteria :: Maybe FilterCriteria
$sel:filterCriteria:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe FilterCriteria
filterCriteria} -> Maybe FilterCriteria
filterCriteria) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe FilterCriteria
a -> CreateEventSourceMapping
s {$sel:filterCriteria:CreateEventSourceMapping' :: Maybe FilterCriteria
filterCriteria = Maybe FilterCriteria
a} :: CreateEventSourceMapping)

-- | (Streams and Amazon SQS) A list of current response type enums applied
-- to the event source mapping.
createEventSourceMapping_functionResponseTypes :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe [FunctionResponseType])
createEventSourceMapping_functionResponseTypes :: Lens' CreateEventSourceMapping (Maybe [FunctionResponseType])
createEventSourceMapping_functionResponseTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe [FunctionResponseType]
functionResponseTypes :: Maybe [FunctionResponseType]
$sel:functionResponseTypes:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [FunctionResponseType]
functionResponseTypes} -> Maybe [FunctionResponseType]
functionResponseTypes) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe [FunctionResponseType]
a -> CreateEventSourceMapping
s {$sel:functionResponseTypes:CreateEventSourceMapping' :: Maybe [FunctionResponseType]
functionResponseTypes = Maybe [FunctionResponseType]
a} :: CreateEventSourceMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The maximum amount of time, in seconds, that Lambda spends gathering
-- records before invoking the function. You can configure
-- @MaximumBatchingWindowInSeconds@ to any value from 0 seconds to 300
-- seconds in increments of seconds.
--
-- For streams and Amazon SQS event sources, the default batching window is
-- 0 seconds. For Amazon MSK, Self-managed Apache Kafka, and Amazon MQ
-- event sources, the default batching window is 500 ms. Note that because
-- you can only change @MaximumBatchingWindowInSeconds@ in increments of
-- seconds, you cannot revert back to the 500 ms default batching window
-- after you have changed it. To restore the default batching window, you
-- must create a new event source mapping.
--
-- Related setting: For streams and Amazon SQS event sources, when you set
-- @BatchSize@ to a value greater than 10, you must set
-- @MaximumBatchingWindowInSeconds@ to at least 1.
createEventSourceMapping_maximumBatchingWindowInSeconds :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Natural)
createEventSourceMapping_maximumBatchingWindowInSeconds :: Lens' CreateEventSourceMapping (Maybe Natural)
createEventSourceMapping_maximumBatchingWindowInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Natural
maximumBatchingWindowInSeconds :: Maybe Natural
$sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
maximumBatchingWindowInSeconds} -> Maybe Natural
maximumBatchingWindowInSeconds) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Natural
a -> CreateEventSourceMapping
s {$sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: Maybe Natural
maximumBatchingWindowInSeconds = Maybe Natural
a} :: CreateEventSourceMapping)

-- | (Streams only) Discard records older than the specified age. The default
-- value is infinite (-1).
createEventSourceMapping_maximumRecordAgeInSeconds :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Int)
createEventSourceMapping_maximumRecordAgeInSeconds :: Lens' CreateEventSourceMapping (Maybe Int)
createEventSourceMapping_maximumRecordAgeInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Int
maximumRecordAgeInSeconds :: Maybe Int
$sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
maximumRecordAgeInSeconds} -> Maybe Int
maximumRecordAgeInSeconds) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Int
a -> CreateEventSourceMapping
s {$sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: Maybe Int
maximumRecordAgeInSeconds = Maybe Int
a} :: CreateEventSourceMapping)

-- | (Streams only) Discard records after the specified number of retries.
-- The default value is infinite (-1). When set to infinite (-1), failed
-- records are retried until the record expires.
createEventSourceMapping_maximumRetryAttempts :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Int)
createEventSourceMapping_maximumRetryAttempts :: Lens' CreateEventSourceMapping (Maybe Int)
createEventSourceMapping_maximumRetryAttempts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Int
maximumRetryAttempts :: Maybe Int
$sel:maximumRetryAttempts:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
maximumRetryAttempts} -> Maybe Int
maximumRetryAttempts) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Int
a -> CreateEventSourceMapping
s {$sel:maximumRetryAttempts:CreateEventSourceMapping' :: Maybe Int
maximumRetryAttempts = Maybe Int
a} :: CreateEventSourceMapping)

-- | (Streams only) The number of batches to process from each shard
-- concurrently.
createEventSourceMapping_parallelizationFactor :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Natural)
createEventSourceMapping_parallelizationFactor :: Lens' CreateEventSourceMapping (Maybe Natural)
createEventSourceMapping_parallelizationFactor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Natural
parallelizationFactor :: Maybe Natural
$sel:parallelizationFactor:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
parallelizationFactor} -> Maybe Natural
parallelizationFactor) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Natural
a -> CreateEventSourceMapping
s {$sel:parallelizationFactor:CreateEventSourceMapping' :: Maybe Natural
parallelizationFactor = Maybe Natural
a} :: CreateEventSourceMapping)

-- | (MQ) The name of the Amazon MQ broker destination queue to consume.
createEventSourceMapping_queues :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
createEventSourceMapping_queues :: Lens' CreateEventSourceMapping (Maybe (NonEmpty Text))
createEventSourceMapping_queues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe (NonEmpty Text)
queues :: Maybe (NonEmpty Text)
$sel:queues:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
queues} -> Maybe (NonEmpty Text)
queues) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe (NonEmpty Text)
a -> CreateEventSourceMapping
s {$sel:queues:CreateEventSourceMapping' :: Maybe (NonEmpty Text)
queues = Maybe (NonEmpty Text)
a} :: CreateEventSourceMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The self-managed Apache Kafka cluster to receive records from.
createEventSourceMapping_selfManagedEventSource :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe SelfManagedEventSource)
createEventSourceMapping_selfManagedEventSource :: Lens' CreateEventSourceMapping (Maybe SelfManagedEventSource)
createEventSourceMapping_selfManagedEventSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe SelfManagedEventSource
selfManagedEventSource :: Maybe SelfManagedEventSource
$sel:selfManagedEventSource:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedEventSource
selfManagedEventSource} -> Maybe SelfManagedEventSource
selfManagedEventSource) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe SelfManagedEventSource
a -> CreateEventSourceMapping
s {$sel:selfManagedEventSource:CreateEventSourceMapping' :: Maybe SelfManagedEventSource
selfManagedEventSource = Maybe SelfManagedEventSource
a} :: CreateEventSourceMapping)

-- | Specific configuration settings for a self-managed Apache Kafka event
-- source.
createEventSourceMapping_selfManagedKafkaEventSourceConfig :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe SelfManagedKafkaEventSourceConfig)
createEventSourceMapping_selfManagedKafkaEventSourceConfig :: Lens'
  CreateEventSourceMapping (Maybe SelfManagedKafkaEventSourceConfig)
createEventSourceMapping_selfManagedKafkaEventSourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig :: Maybe SelfManagedKafkaEventSourceConfig
$sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig} -> Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe SelfManagedKafkaEventSourceConfig
a -> CreateEventSourceMapping
s {$sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig = Maybe SelfManagedKafkaEventSourceConfig
a} :: CreateEventSourceMapping)

-- | An array of authentication protocols or VPC components required to
-- secure your event source.
createEventSourceMapping_sourceAccessConfigurations :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe [SourceAccessConfiguration])
createEventSourceMapping_sourceAccessConfigurations :: Lens' CreateEventSourceMapping (Maybe [SourceAccessConfiguration])
createEventSourceMapping_sourceAccessConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe [SourceAccessConfiguration]
sourceAccessConfigurations :: Maybe [SourceAccessConfiguration]
$sel:sourceAccessConfigurations:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [SourceAccessConfiguration]
sourceAccessConfigurations} -> Maybe [SourceAccessConfiguration]
sourceAccessConfigurations) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe [SourceAccessConfiguration]
a -> CreateEventSourceMapping
s {$sel:sourceAccessConfigurations:CreateEventSourceMapping' :: Maybe [SourceAccessConfiguration]
sourceAccessConfigurations = Maybe [SourceAccessConfiguration]
a} :: CreateEventSourceMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The position in a stream from which to start reading. Required for
-- Amazon Kinesis, Amazon DynamoDB, and Amazon MSK Streams sources.
-- @AT_TIMESTAMP@ is supported only for Amazon Kinesis streams.
createEventSourceMapping_startingPosition :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe EventSourcePosition)
createEventSourceMapping_startingPosition :: Lens' CreateEventSourceMapping (Maybe EventSourcePosition)
createEventSourceMapping_startingPosition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe EventSourcePosition
startingPosition :: Maybe EventSourcePosition
$sel:startingPosition:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe EventSourcePosition
startingPosition} -> Maybe EventSourcePosition
startingPosition) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe EventSourcePosition
a -> CreateEventSourceMapping
s {$sel:startingPosition:CreateEventSourceMapping' :: Maybe EventSourcePosition
startingPosition = Maybe EventSourcePosition
a} :: CreateEventSourceMapping)

-- | With @StartingPosition@ set to @AT_TIMESTAMP@, the time from which to
-- start reading.
createEventSourceMapping_startingPositionTimestamp :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.UTCTime)
createEventSourceMapping_startingPositionTimestamp :: Lens' CreateEventSourceMapping (Maybe UTCTime)
createEventSourceMapping_startingPositionTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe POSIX
startingPositionTimestamp :: Maybe POSIX
$sel:startingPositionTimestamp:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe POSIX
startingPositionTimestamp} -> Maybe POSIX
startingPositionTimestamp) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe POSIX
a -> CreateEventSourceMapping
s {$sel:startingPositionTimestamp:CreateEventSourceMapping' :: Maybe POSIX
startingPositionTimestamp = Maybe POSIX
a} :: CreateEventSourceMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the Kafka topic.
createEventSourceMapping_topics :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
createEventSourceMapping_topics :: Lens' CreateEventSourceMapping (Maybe (NonEmpty Text))
createEventSourceMapping_topics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe (NonEmpty Text)
topics :: Maybe (NonEmpty Text)
$sel:topics:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
topics} -> Maybe (NonEmpty Text)
topics) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe (NonEmpty Text)
a -> CreateEventSourceMapping
s {$sel:topics:CreateEventSourceMapping' :: Maybe (NonEmpty Text)
topics = Maybe (NonEmpty Text)
a} :: CreateEventSourceMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | (Streams only) The duration in seconds of a processing window. The range
-- is between 1 second and 900 seconds.
createEventSourceMapping_tumblingWindowInSeconds :: Lens.Lens' CreateEventSourceMapping (Prelude.Maybe Prelude.Natural)
createEventSourceMapping_tumblingWindowInSeconds :: Lens' CreateEventSourceMapping (Maybe Natural)
createEventSourceMapping_tumblingWindowInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Maybe Natural
tumblingWindowInSeconds :: Maybe Natural
$sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
tumblingWindowInSeconds} -> Maybe Natural
tumblingWindowInSeconds) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Maybe Natural
a -> CreateEventSourceMapping
s {$sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: Maybe Natural
tumblingWindowInSeconds = Maybe Natural
a} :: CreateEventSourceMapping)

-- | The name of the Lambda function.
--
-- __Name formats__
--
-- -   __Function name__ - @MyFunction@.
--
-- -   __Function ARN__ -
--     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction@.
--
-- -   __Version or Alias ARN__ -
--     @arn:aws:lambda:us-west-2:123456789012:function:MyFunction:PROD@.
--
-- -   __Partial ARN__ - @123456789012:function:MyFunction@.
--
-- The length constraint applies only to the full ARN. If you specify only
-- the function name, it\'s limited to 64 characters in length.
createEventSourceMapping_functionName :: Lens.Lens' CreateEventSourceMapping Prelude.Text
createEventSourceMapping_functionName :: Lens' CreateEventSourceMapping Text
createEventSourceMapping_functionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSourceMapping' {Text
functionName :: Text
$sel:functionName:CreateEventSourceMapping' :: CreateEventSourceMapping -> Text
functionName} -> Text
functionName) (\s :: CreateEventSourceMapping
s@CreateEventSourceMapping' {} Text
a -> CreateEventSourceMapping
s {$sel:functionName:CreateEventSourceMapping' :: Text
functionName = Text
a} :: CreateEventSourceMapping)

instance Core.AWSRequest CreateEventSourceMapping where
  type
    AWSResponse CreateEventSourceMapping =
      EventSourceMappingConfiguration
  request :: (Service -> Service)
-> CreateEventSourceMapping -> Request CreateEventSourceMapping
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateEventSourceMapping
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateEventSourceMapping)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      (\Int
s ResponseHeaders
h Object
x -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable CreateEventSourceMapping where
  hashWithSalt :: Int -> CreateEventSourceMapping -> Int
hashWithSalt Int
_salt CreateEventSourceMapping' {Maybe Bool
Maybe Int
Maybe Natural
Maybe [FunctionResponseType]
Maybe [SourceAccessConfiguration]
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe AmazonManagedKafkaEventSourceConfig
Maybe EventSourcePosition
Maybe FilterCriteria
Maybe DestinationConfig
Maybe SelfManagedEventSource
Maybe SelfManagedKafkaEventSourceConfig
Text
functionName :: Text
tumblingWindowInSeconds :: Maybe Natural
topics :: Maybe (NonEmpty Text)
startingPositionTimestamp :: Maybe POSIX
startingPosition :: Maybe EventSourcePosition
sourceAccessConfigurations :: Maybe [SourceAccessConfiguration]
selfManagedKafkaEventSourceConfig :: Maybe SelfManagedKafkaEventSourceConfig
selfManagedEventSource :: Maybe SelfManagedEventSource
queues :: Maybe (NonEmpty Text)
parallelizationFactor :: Maybe Natural
maximumRetryAttempts :: Maybe Int
maximumRecordAgeInSeconds :: Maybe Int
maximumBatchingWindowInSeconds :: Maybe Natural
functionResponseTypes :: Maybe [FunctionResponseType]
filterCriteria :: Maybe FilterCriteria
eventSourceArn :: Maybe Text
enabled :: Maybe Bool
destinationConfig :: Maybe DestinationConfig
bisectBatchOnFunctionError :: Maybe Bool
batchSize :: Maybe Natural
amazonManagedKafkaEventSourceConfig :: Maybe AmazonManagedKafkaEventSourceConfig
$sel:functionName:CreateEventSourceMapping' :: CreateEventSourceMapping -> Text
$sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:topics:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:startingPositionTimestamp:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe POSIX
$sel:startingPosition:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe EventSourcePosition
$sel:sourceAccessConfigurations:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [SourceAccessConfiguration]
$sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedKafkaEventSourceConfig
$sel:selfManagedEventSource:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedEventSource
$sel:queues:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:parallelizationFactor:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:maximumRetryAttempts:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:functionResponseTypes:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [FunctionResponseType]
$sel:filterCriteria:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe FilterCriteria
$sel:eventSourceArn:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Text
$sel:enabled:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:destinationConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe DestinationConfig
$sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:batchSize:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping
-> Maybe AmazonManagedKafkaEventSourceConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
batchSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
bisectBatchOnFunctionError
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DestinationConfig
destinationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eventSourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FilterCriteria
filterCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FunctionResponseType]
functionResponseTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maximumBatchingWindowInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maximumRecordAgeInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maximumRetryAttempts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
parallelizationFactor
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
queues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SelfManagedEventSource
selfManagedEventSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SourceAccessConfiguration]
sourceAccessConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EventSourcePosition
startingPosition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startingPositionTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
topics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
tumblingWindowInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
functionName

instance Prelude.NFData CreateEventSourceMapping where
  rnf :: CreateEventSourceMapping -> ()
rnf CreateEventSourceMapping' {Maybe Bool
Maybe Int
Maybe Natural
Maybe [FunctionResponseType]
Maybe [SourceAccessConfiguration]
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe AmazonManagedKafkaEventSourceConfig
Maybe EventSourcePosition
Maybe FilterCriteria
Maybe DestinationConfig
Maybe SelfManagedEventSource
Maybe SelfManagedKafkaEventSourceConfig
Text
functionName :: Text
tumblingWindowInSeconds :: Maybe Natural
topics :: Maybe (NonEmpty Text)
startingPositionTimestamp :: Maybe POSIX
startingPosition :: Maybe EventSourcePosition
sourceAccessConfigurations :: Maybe [SourceAccessConfiguration]
selfManagedKafkaEventSourceConfig :: Maybe SelfManagedKafkaEventSourceConfig
selfManagedEventSource :: Maybe SelfManagedEventSource
queues :: Maybe (NonEmpty Text)
parallelizationFactor :: Maybe Natural
maximumRetryAttempts :: Maybe Int
maximumRecordAgeInSeconds :: Maybe Int
maximumBatchingWindowInSeconds :: Maybe Natural
functionResponseTypes :: Maybe [FunctionResponseType]
filterCriteria :: Maybe FilterCriteria
eventSourceArn :: Maybe Text
enabled :: Maybe Bool
destinationConfig :: Maybe DestinationConfig
bisectBatchOnFunctionError :: Maybe Bool
batchSize :: Maybe Natural
amazonManagedKafkaEventSourceConfig :: Maybe AmazonManagedKafkaEventSourceConfig
$sel:functionName:CreateEventSourceMapping' :: CreateEventSourceMapping -> Text
$sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:topics:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:startingPositionTimestamp:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe POSIX
$sel:startingPosition:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe EventSourcePosition
$sel:sourceAccessConfigurations:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [SourceAccessConfiguration]
$sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedKafkaEventSourceConfig
$sel:selfManagedEventSource:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedEventSource
$sel:queues:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:parallelizationFactor:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:maximumRetryAttempts:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:functionResponseTypes:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [FunctionResponseType]
$sel:filterCriteria:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe FilterCriteria
$sel:eventSourceArn:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Text
$sel:enabled:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:destinationConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe DestinationConfig
$sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:batchSize:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping
-> Maybe AmazonManagedKafkaEventSourceConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
batchSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
bisectBatchOnFunctionError
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DestinationConfig
destinationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventSourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FilterCriteria
filterCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [FunctionResponseType]
functionResponseTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maximumBatchingWindowInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maximumRecordAgeInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maximumRetryAttempts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
parallelizationFactor
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
queues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SelfManagedEventSource
selfManagedEventSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SourceAccessConfiguration]
sourceAccessConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EventSourcePosition
startingPosition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
startingPositionTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
topics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Natural
tumblingWindowInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionName

instance Data.ToHeaders CreateEventSourceMapping where
  toHeaders :: CreateEventSourceMapping -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateEventSourceMapping where
  toJSON :: CreateEventSourceMapping -> Value
toJSON CreateEventSourceMapping' {Maybe Bool
Maybe Int
Maybe Natural
Maybe [FunctionResponseType]
Maybe [SourceAccessConfiguration]
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe AmazonManagedKafkaEventSourceConfig
Maybe EventSourcePosition
Maybe FilterCriteria
Maybe DestinationConfig
Maybe SelfManagedEventSource
Maybe SelfManagedKafkaEventSourceConfig
Text
functionName :: Text
tumblingWindowInSeconds :: Maybe Natural
topics :: Maybe (NonEmpty Text)
startingPositionTimestamp :: Maybe POSIX
startingPosition :: Maybe EventSourcePosition
sourceAccessConfigurations :: Maybe [SourceAccessConfiguration]
selfManagedKafkaEventSourceConfig :: Maybe SelfManagedKafkaEventSourceConfig
selfManagedEventSource :: Maybe SelfManagedEventSource
queues :: Maybe (NonEmpty Text)
parallelizationFactor :: Maybe Natural
maximumRetryAttempts :: Maybe Int
maximumRecordAgeInSeconds :: Maybe Int
maximumBatchingWindowInSeconds :: Maybe Natural
functionResponseTypes :: Maybe [FunctionResponseType]
filterCriteria :: Maybe FilterCriteria
eventSourceArn :: Maybe Text
enabled :: Maybe Bool
destinationConfig :: Maybe DestinationConfig
bisectBatchOnFunctionError :: Maybe Bool
batchSize :: Maybe Natural
amazonManagedKafkaEventSourceConfig :: Maybe AmazonManagedKafkaEventSourceConfig
$sel:functionName:CreateEventSourceMapping' :: CreateEventSourceMapping -> Text
$sel:tumblingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:topics:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:startingPositionTimestamp:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe POSIX
$sel:startingPosition:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe EventSourcePosition
$sel:sourceAccessConfigurations:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [SourceAccessConfiguration]
$sel:selfManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedKafkaEventSourceConfig
$sel:selfManagedEventSource:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe SelfManagedEventSource
$sel:queues:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe (NonEmpty Text)
$sel:parallelizationFactor:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:maximumRetryAttempts:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumRecordAgeInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Int
$sel:maximumBatchingWindowInSeconds:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:functionResponseTypes:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe [FunctionResponseType]
$sel:filterCriteria:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe FilterCriteria
$sel:eventSourceArn:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Text
$sel:enabled:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:destinationConfig:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe DestinationConfig
$sel:bisectBatchOnFunctionError:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Bool
$sel:batchSize:CreateEventSourceMapping' :: CreateEventSourceMapping -> Maybe Natural
$sel:amazonManagedKafkaEventSourceConfig:CreateEventSourceMapping' :: CreateEventSourceMapping
-> Maybe AmazonManagedKafkaEventSourceConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AmazonManagedKafkaEventSourceConfig" 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 AmazonManagedKafkaEventSourceConfig
amazonManagedKafkaEventSourceConfig,
            (Key
"BatchSize" 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
batchSize,
            (Key
"BisectBatchOnFunctionError" 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 Bool
bisectBatchOnFunctionError,
            (Key
"DestinationConfig" 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 DestinationConfig
destinationConfig,
            (Key
"Enabled" 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 Bool
enabled,
            (Key
"EventSourceArn" 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
eventSourceArn,
            (Key
"FilterCriteria" 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 FilterCriteria
filterCriteria,
            (Key
"FunctionResponseTypes" 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 [FunctionResponseType]
functionResponseTypes,
            (Key
"MaximumBatchingWindowInSeconds" 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
maximumBatchingWindowInSeconds,
            (Key
"MaximumRecordAgeInSeconds" 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 Int
maximumRecordAgeInSeconds,
            (Key
"MaximumRetryAttempts" 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 Int
maximumRetryAttempts,
            (Key
"ParallelizationFactor" 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
parallelizationFactor,
            (Key
"Queues" 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 (NonEmpty Text)
queues,
            (Key
"SelfManagedEventSource" 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 SelfManagedEventSource
selfManagedEventSource,
            (Key
"SelfManagedKafkaEventSourceConfig" 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 SelfManagedKafkaEventSourceConfig
selfManagedKafkaEventSourceConfig,
            (Key
"SourceAccessConfigurations" 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 [SourceAccessConfiguration]
sourceAccessConfigurations,
            (Key
"StartingPosition" 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 EventSourcePosition
startingPosition,
            (Key
"StartingPositionTimestamp" 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 POSIX
startingPositionTimestamp,
            (Key
"Topics" 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 (NonEmpty Text)
topics,
            (Key
"TumblingWindowInSeconds" 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
tumblingWindowInSeconds,
            forall a. a -> Maybe a
Prelude.Just (Key
"FunctionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
functionName)
          ]
      )

instance Data.ToPath CreateEventSourceMapping where
  toPath :: CreateEventSourceMapping -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/2015-03-31/event-source-mappings/"

instance Data.ToQuery CreateEventSourceMapping where
  toQuery :: CreateEventSourceMapping -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty