{-# 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.Glue.Types.KinesisStreamingSourceOptions
-- 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.Glue.Types.KinesisStreamingSourceOptions where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types.StartingPosition
import qualified Amazonka.Prelude as Prelude

-- | Additional options for the Amazon Kinesis streaming data source.
--
-- /See:/ 'newKinesisStreamingSourceOptions' smart constructor.
data KinesisStreamingSourceOptions = KinesisStreamingSourceOptions'
  { -- | Adds a time delay between two consecutive getRecords operations. The
    -- default value is @\"False\"@. This option is only configurable for Glue
    -- version 2.0 and above.
    KinesisStreamingSourceOptions -> Maybe Bool
addIdleTimeBetweenReads :: Prelude.Maybe Prelude.Bool,
    -- | Avoids creating an empty microbatch job by checking for unread data in
    -- the Kinesis data stream before the batch is started. The default value
    -- is @\"False\"@.
    KinesisStreamingSourceOptions -> Maybe Bool
avoidEmptyBatches :: Prelude.Maybe Prelude.Bool,
    -- | An optional classification.
    KinesisStreamingSourceOptions -> Maybe Text
classification :: Prelude.Maybe Prelude.Text,
    -- | Specifies the delimiter character.
    KinesisStreamingSourceOptions -> Maybe Text
delimiter :: Prelude.Maybe Prelude.Text,
    -- | The minimum time interval between two ListShards API calls for your
    -- script to consider resharding. The default value is @1s@.
    KinesisStreamingSourceOptions -> Maybe Natural
describeShardInterval :: Prelude.Maybe Prelude.Natural,
    -- | The URL of the Kinesis endpoint.
    KinesisStreamingSourceOptions -> Maybe Text
endpointUrl :: Prelude.Maybe Prelude.Text,
    -- | The minimum time delay between two consecutive getRecords operations,
    -- specified in ms. The default value is @1000@. This option is only
    -- configurable for Glue version 2.0 and above.
    KinesisStreamingSourceOptions -> Maybe Natural
idleTimeBetweenReadsInMs :: Prelude.Maybe Prelude.Natural,
    -- | The maximum number of records to fetch per shard in the Kinesis data
    -- stream. The default value is @100000@.
    KinesisStreamingSourceOptions -> Maybe Natural
maxFetchRecordsPerShard :: Prelude.Maybe Prelude.Natural,
    -- | The maximum time spent in the job executor to fetch a record from the
    -- Kinesis data stream per shard, specified in milliseconds (ms). The
    -- default value is @1000@.
    KinesisStreamingSourceOptions -> Maybe Natural
maxFetchTimeInMs :: Prelude.Maybe Prelude.Natural,
    -- | The maximum number of records to fetch from the Kinesis data stream in
    -- each getRecords operation. The default value is @10000@.
    KinesisStreamingSourceOptions -> Maybe Natural
maxRecordPerRead :: Prelude.Maybe Prelude.Natural,
    -- | The maximum cool-off time period (specified in ms) between two retries
    -- of a Kinesis Data Streams API call. The default value is @10000@.
    KinesisStreamingSourceOptions -> Maybe Natural
maxRetryIntervalMs :: Prelude.Maybe Prelude.Natural,
    -- | The maximum number of retries for Kinesis Data Streams API requests. The
    -- default value is @3@.
    KinesisStreamingSourceOptions -> Maybe Natural
numRetries :: Prelude.Maybe Prelude.Natural,
    -- | The cool-off time period (specified in ms) before retrying the Kinesis
    -- Data Streams API call. The default value is @1000@.
    KinesisStreamingSourceOptions -> Maybe Natural
retryIntervalMs :: Prelude.Maybe Prelude.Natural,
    -- | The Amazon Resource Name (ARN) of the role to assume using AWS Security
    -- Token Service (AWS STS). This role must have permissions for describe or
    -- read record operations for the Kinesis data stream. You must use this
    -- parameter when accessing a data stream in a different account. Used in
    -- conjunction with @\"awsSTSSessionName\"@.
    KinesisStreamingSourceOptions -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | An identifier for the session assuming the role using AWS STS. You must
    -- use this parameter when accessing a data stream in a different account.
    -- Used in conjunction with @\"awsSTSRoleARN\"@.
    KinesisStreamingSourceOptions -> Maybe Text
roleSessionName :: Prelude.Maybe Prelude.Text,
    -- | The starting position in the Kinesis data stream to read data from. The
    -- possible values are @\"latest\"@, @\"trim_horizon\"@, or @\"earliest\"@.
    -- The default value is @\"latest\"@.
    KinesisStreamingSourceOptions -> Maybe StartingPosition
startingPosition :: Prelude.Maybe StartingPosition,
    -- | The Amazon Resource Name (ARN) of the Kinesis data stream.
    KinesisStreamingSourceOptions -> Maybe Text
streamArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the Kinesis data stream.
    KinesisStreamingSourceOptions -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text
  }
  deriving (KinesisStreamingSourceOptions
-> KinesisStreamingSourceOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KinesisStreamingSourceOptions
-> KinesisStreamingSourceOptions -> Bool
$c/= :: KinesisStreamingSourceOptions
-> KinesisStreamingSourceOptions -> Bool
== :: KinesisStreamingSourceOptions
-> KinesisStreamingSourceOptions -> Bool
$c== :: KinesisStreamingSourceOptions
-> KinesisStreamingSourceOptions -> Bool
Prelude.Eq, ReadPrec [KinesisStreamingSourceOptions]
ReadPrec KinesisStreamingSourceOptions
Int -> ReadS KinesisStreamingSourceOptions
ReadS [KinesisStreamingSourceOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KinesisStreamingSourceOptions]
$creadListPrec :: ReadPrec [KinesisStreamingSourceOptions]
readPrec :: ReadPrec KinesisStreamingSourceOptions
$creadPrec :: ReadPrec KinesisStreamingSourceOptions
readList :: ReadS [KinesisStreamingSourceOptions]
$creadList :: ReadS [KinesisStreamingSourceOptions]
readsPrec :: Int -> ReadS KinesisStreamingSourceOptions
$creadsPrec :: Int -> ReadS KinesisStreamingSourceOptions
Prelude.Read, Int -> KinesisStreamingSourceOptions -> ShowS
[KinesisStreamingSourceOptions] -> ShowS
KinesisStreamingSourceOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KinesisStreamingSourceOptions] -> ShowS
$cshowList :: [KinesisStreamingSourceOptions] -> ShowS
show :: KinesisStreamingSourceOptions -> String
$cshow :: KinesisStreamingSourceOptions -> String
showsPrec :: Int -> KinesisStreamingSourceOptions -> ShowS
$cshowsPrec :: Int -> KinesisStreamingSourceOptions -> ShowS
Prelude.Show, forall x.
Rep KinesisStreamingSourceOptions x
-> KinesisStreamingSourceOptions
forall x.
KinesisStreamingSourceOptions
-> Rep KinesisStreamingSourceOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep KinesisStreamingSourceOptions x
-> KinesisStreamingSourceOptions
$cfrom :: forall x.
KinesisStreamingSourceOptions
-> Rep KinesisStreamingSourceOptions x
Prelude.Generic)

-- |
-- Create a value of 'KinesisStreamingSourceOptions' 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:
--
-- 'addIdleTimeBetweenReads', 'kinesisStreamingSourceOptions_addIdleTimeBetweenReads' - Adds a time delay between two consecutive getRecords operations. The
-- default value is @\"False\"@. This option is only configurable for Glue
-- version 2.0 and above.
--
-- 'avoidEmptyBatches', 'kinesisStreamingSourceOptions_avoidEmptyBatches' - Avoids creating an empty microbatch job by checking for unread data in
-- the Kinesis data stream before the batch is started. The default value
-- is @\"False\"@.
--
-- 'classification', 'kinesisStreamingSourceOptions_classification' - An optional classification.
--
-- 'delimiter', 'kinesisStreamingSourceOptions_delimiter' - Specifies the delimiter character.
--
-- 'describeShardInterval', 'kinesisStreamingSourceOptions_describeShardInterval' - The minimum time interval between two ListShards API calls for your
-- script to consider resharding. The default value is @1s@.
--
-- 'endpointUrl', 'kinesisStreamingSourceOptions_endpointUrl' - The URL of the Kinesis endpoint.
--
-- 'idleTimeBetweenReadsInMs', 'kinesisStreamingSourceOptions_idleTimeBetweenReadsInMs' - The minimum time delay between two consecutive getRecords operations,
-- specified in ms. The default value is @1000@. This option is only
-- configurable for Glue version 2.0 and above.
--
-- 'maxFetchRecordsPerShard', 'kinesisStreamingSourceOptions_maxFetchRecordsPerShard' - The maximum number of records to fetch per shard in the Kinesis data
-- stream. The default value is @100000@.
--
-- 'maxFetchTimeInMs', 'kinesisStreamingSourceOptions_maxFetchTimeInMs' - The maximum time spent in the job executor to fetch a record from the
-- Kinesis data stream per shard, specified in milliseconds (ms). The
-- default value is @1000@.
--
-- 'maxRecordPerRead', 'kinesisStreamingSourceOptions_maxRecordPerRead' - The maximum number of records to fetch from the Kinesis data stream in
-- each getRecords operation. The default value is @10000@.
--
-- 'maxRetryIntervalMs', 'kinesisStreamingSourceOptions_maxRetryIntervalMs' - The maximum cool-off time period (specified in ms) between two retries
-- of a Kinesis Data Streams API call. The default value is @10000@.
--
-- 'numRetries', 'kinesisStreamingSourceOptions_numRetries' - The maximum number of retries for Kinesis Data Streams API requests. The
-- default value is @3@.
--
-- 'retryIntervalMs', 'kinesisStreamingSourceOptions_retryIntervalMs' - The cool-off time period (specified in ms) before retrying the Kinesis
-- Data Streams API call. The default value is @1000@.
--
-- 'roleArn', 'kinesisStreamingSourceOptions_roleArn' - The Amazon Resource Name (ARN) of the role to assume using AWS Security
-- Token Service (AWS STS). This role must have permissions for describe or
-- read record operations for the Kinesis data stream. You must use this
-- parameter when accessing a data stream in a different account. Used in
-- conjunction with @\"awsSTSSessionName\"@.
--
-- 'roleSessionName', 'kinesisStreamingSourceOptions_roleSessionName' - An identifier for the session assuming the role using AWS STS. You must
-- use this parameter when accessing a data stream in a different account.
-- Used in conjunction with @\"awsSTSRoleARN\"@.
--
-- 'startingPosition', 'kinesisStreamingSourceOptions_startingPosition' - The starting position in the Kinesis data stream to read data from. The
-- possible values are @\"latest\"@, @\"trim_horizon\"@, or @\"earliest\"@.
-- The default value is @\"latest\"@.
--
-- 'streamArn', 'kinesisStreamingSourceOptions_streamArn' - The Amazon Resource Name (ARN) of the Kinesis data stream.
--
-- 'streamName', 'kinesisStreamingSourceOptions_streamName' - The name of the Kinesis data stream.
newKinesisStreamingSourceOptions ::
  KinesisStreamingSourceOptions
newKinesisStreamingSourceOptions :: KinesisStreamingSourceOptions
newKinesisStreamingSourceOptions =
  KinesisStreamingSourceOptions'
    { $sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: Maybe Bool
addIdleTimeBetweenReads =
        forall a. Maybe a
Prelude.Nothing,
      $sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: Maybe Bool
avoidEmptyBatches = forall a. Maybe a
Prelude.Nothing,
      $sel:classification:KinesisStreamingSourceOptions' :: Maybe Text
classification = forall a. Maybe a
Prelude.Nothing,
      $sel:delimiter:KinesisStreamingSourceOptions' :: Maybe Text
delimiter = forall a. Maybe a
Prelude.Nothing,
      $sel:describeShardInterval:KinesisStreamingSourceOptions' :: Maybe Natural
describeShardInterval = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointUrl:KinesisStreamingSourceOptions' :: Maybe Text
endpointUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: Maybe Natural
idleTimeBetweenReadsInMs = forall a. Maybe a
Prelude.Nothing,
      $sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: Maybe Natural
maxFetchRecordsPerShard = forall a. Maybe a
Prelude.Nothing,
      $sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: Maybe Natural
maxFetchTimeInMs = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: Maybe Natural
maxRecordPerRead = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: Maybe Natural
maxRetryIntervalMs = forall a. Maybe a
Prelude.Nothing,
      $sel:numRetries:KinesisStreamingSourceOptions' :: Maybe Natural
numRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:retryIntervalMs:KinesisStreamingSourceOptions' :: Maybe Natural
retryIntervalMs = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:KinesisStreamingSourceOptions' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:roleSessionName:KinesisStreamingSourceOptions' :: Maybe Text
roleSessionName = forall a. Maybe a
Prelude.Nothing,
      $sel:startingPosition:KinesisStreamingSourceOptions' :: Maybe StartingPosition
startingPosition = forall a. Maybe a
Prelude.Nothing,
      $sel:streamArn:KinesisStreamingSourceOptions' :: Maybe Text
streamArn = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:KinesisStreamingSourceOptions' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing
    }

-- | Adds a time delay between two consecutive getRecords operations. The
-- default value is @\"False\"@. This option is only configurable for Glue
-- version 2.0 and above.
kinesisStreamingSourceOptions_addIdleTimeBetweenReads :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Bool)
kinesisStreamingSourceOptions_addIdleTimeBetweenReads :: Lens' KinesisStreamingSourceOptions (Maybe Bool)
kinesisStreamingSourceOptions_addIdleTimeBetweenReads = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Bool
addIdleTimeBetweenReads :: Maybe Bool
$sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
addIdleTimeBetweenReads} -> Maybe Bool
addIdleTimeBetweenReads) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Bool
a -> KinesisStreamingSourceOptions
s {$sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: Maybe Bool
addIdleTimeBetweenReads = Maybe Bool
a} :: KinesisStreamingSourceOptions)

-- | Avoids creating an empty microbatch job by checking for unread data in
-- the Kinesis data stream before the batch is started. The default value
-- is @\"False\"@.
kinesisStreamingSourceOptions_avoidEmptyBatches :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Bool)
kinesisStreamingSourceOptions_avoidEmptyBatches :: Lens' KinesisStreamingSourceOptions (Maybe Bool)
kinesisStreamingSourceOptions_avoidEmptyBatches = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Bool
avoidEmptyBatches :: Maybe Bool
$sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
avoidEmptyBatches} -> Maybe Bool
avoidEmptyBatches) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Bool
a -> KinesisStreamingSourceOptions
s {$sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: Maybe Bool
avoidEmptyBatches = Maybe Bool
a} :: KinesisStreamingSourceOptions)

-- | An optional classification.
kinesisStreamingSourceOptions_classification :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_classification :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_classification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
classification :: Maybe Text
$sel:classification:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
classification} -> Maybe Text
classification) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:classification:KinesisStreamingSourceOptions' :: Maybe Text
classification = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | Specifies the delimiter character.
kinesisStreamingSourceOptions_delimiter :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_delimiter :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_delimiter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
delimiter :: Maybe Text
$sel:delimiter:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
delimiter} -> Maybe Text
delimiter) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:delimiter:KinesisStreamingSourceOptions' :: Maybe Text
delimiter = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | The minimum time interval between two ListShards API calls for your
-- script to consider resharding. The default value is @1s@.
kinesisStreamingSourceOptions_describeShardInterval :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_describeShardInterval :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_describeShardInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
describeShardInterval :: Maybe Natural
$sel:describeShardInterval:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
describeShardInterval} -> Maybe Natural
describeShardInterval) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:describeShardInterval:KinesisStreamingSourceOptions' :: Maybe Natural
describeShardInterval = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The URL of the Kinesis endpoint.
kinesisStreamingSourceOptions_endpointUrl :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_endpointUrl :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_endpointUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
endpointUrl :: Maybe Text
$sel:endpointUrl:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
endpointUrl} -> Maybe Text
endpointUrl) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:endpointUrl:KinesisStreamingSourceOptions' :: Maybe Text
endpointUrl = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | The minimum time delay between two consecutive getRecords operations,
-- specified in ms. The default value is @1000@. This option is only
-- configurable for Glue version 2.0 and above.
kinesisStreamingSourceOptions_idleTimeBetweenReadsInMs :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_idleTimeBetweenReadsInMs :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_idleTimeBetweenReadsInMs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
idleTimeBetweenReadsInMs :: Maybe Natural
$sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
idleTimeBetweenReadsInMs} -> Maybe Natural
idleTimeBetweenReadsInMs) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: Maybe Natural
idleTimeBetweenReadsInMs = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The maximum number of records to fetch per shard in the Kinesis data
-- stream. The default value is @100000@.
kinesisStreamingSourceOptions_maxFetchRecordsPerShard :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_maxFetchRecordsPerShard :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_maxFetchRecordsPerShard = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
maxFetchRecordsPerShard :: Maybe Natural
$sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
maxFetchRecordsPerShard} -> Maybe Natural
maxFetchRecordsPerShard) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: Maybe Natural
maxFetchRecordsPerShard = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The maximum time spent in the job executor to fetch a record from the
-- Kinesis data stream per shard, specified in milliseconds (ms). The
-- default value is @1000@.
kinesisStreamingSourceOptions_maxFetchTimeInMs :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_maxFetchTimeInMs :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_maxFetchTimeInMs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
maxFetchTimeInMs :: Maybe Natural
$sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
maxFetchTimeInMs} -> Maybe Natural
maxFetchTimeInMs) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: Maybe Natural
maxFetchTimeInMs = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The maximum number of records to fetch from the Kinesis data stream in
-- each getRecords operation. The default value is @10000@.
kinesisStreamingSourceOptions_maxRecordPerRead :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_maxRecordPerRead :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_maxRecordPerRead = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
maxRecordPerRead :: Maybe Natural
$sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
maxRecordPerRead} -> Maybe Natural
maxRecordPerRead) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: Maybe Natural
maxRecordPerRead = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The maximum cool-off time period (specified in ms) between two retries
-- of a Kinesis Data Streams API call. The default value is @10000@.
kinesisStreamingSourceOptions_maxRetryIntervalMs :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_maxRetryIntervalMs :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_maxRetryIntervalMs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
maxRetryIntervalMs :: Maybe Natural
$sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
maxRetryIntervalMs} -> Maybe Natural
maxRetryIntervalMs) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: Maybe Natural
maxRetryIntervalMs = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The maximum number of retries for Kinesis Data Streams API requests. The
-- default value is @3@.
kinesisStreamingSourceOptions_numRetries :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_numRetries :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_numRetries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
numRetries :: Maybe Natural
$sel:numRetries:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
numRetries} -> Maybe Natural
numRetries) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:numRetries:KinesisStreamingSourceOptions' :: Maybe Natural
numRetries = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The cool-off time period (specified in ms) before retrying the Kinesis
-- Data Streams API call. The default value is @1000@.
kinesisStreamingSourceOptions_retryIntervalMs :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Natural)
kinesisStreamingSourceOptions_retryIntervalMs :: Lens' KinesisStreamingSourceOptions (Maybe Natural)
kinesisStreamingSourceOptions_retryIntervalMs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Natural
retryIntervalMs :: Maybe Natural
$sel:retryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
retryIntervalMs} -> Maybe Natural
retryIntervalMs) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Natural
a -> KinesisStreamingSourceOptions
s {$sel:retryIntervalMs:KinesisStreamingSourceOptions' :: Maybe Natural
retryIntervalMs = Maybe Natural
a} :: KinesisStreamingSourceOptions)

-- | The Amazon Resource Name (ARN) of the role to assume using AWS Security
-- Token Service (AWS STS). This role must have permissions for describe or
-- read record operations for the Kinesis data stream. You must use this
-- parameter when accessing a data stream in a different account. Used in
-- conjunction with @\"awsSTSSessionName\"@.
kinesisStreamingSourceOptions_roleArn :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_roleArn :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:roleArn:KinesisStreamingSourceOptions' :: Maybe Text
roleArn = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | An identifier for the session assuming the role using AWS STS. You must
-- use this parameter when accessing a data stream in a different account.
-- Used in conjunction with @\"awsSTSRoleARN\"@.
kinesisStreamingSourceOptions_roleSessionName :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_roleSessionName :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_roleSessionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
roleSessionName :: Maybe Text
$sel:roleSessionName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
roleSessionName} -> Maybe Text
roleSessionName) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:roleSessionName:KinesisStreamingSourceOptions' :: Maybe Text
roleSessionName = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | The starting position in the Kinesis data stream to read data from. The
-- possible values are @\"latest\"@, @\"trim_horizon\"@, or @\"earliest\"@.
-- The default value is @\"latest\"@.
kinesisStreamingSourceOptions_startingPosition :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe StartingPosition)
kinesisStreamingSourceOptions_startingPosition :: Lens' KinesisStreamingSourceOptions (Maybe StartingPosition)
kinesisStreamingSourceOptions_startingPosition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe StartingPosition
startingPosition :: Maybe StartingPosition
$sel:startingPosition:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe StartingPosition
startingPosition} -> Maybe StartingPosition
startingPosition) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe StartingPosition
a -> KinesisStreamingSourceOptions
s {$sel:startingPosition:KinesisStreamingSourceOptions' :: Maybe StartingPosition
startingPosition = Maybe StartingPosition
a} :: KinesisStreamingSourceOptions)

-- | The Amazon Resource Name (ARN) of the Kinesis data stream.
kinesisStreamingSourceOptions_streamArn :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_streamArn :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_streamArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
streamArn :: Maybe Text
$sel:streamArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
streamArn} -> Maybe Text
streamArn) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:streamArn:KinesisStreamingSourceOptions' :: Maybe Text
streamArn = Maybe Text
a} :: KinesisStreamingSourceOptions)

-- | The name of the Kinesis data stream.
kinesisStreamingSourceOptions_streamName :: Lens.Lens' KinesisStreamingSourceOptions (Prelude.Maybe Prelude.Text)
kinesisStreamingSourceOptions_streamName :: Lens' KinesisStreamingSourceOptions (Maybe Text)
kinesisStreamingSourceOptions_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KinesisStreamingSourceOptions' {Maybe Text
streamName :: Maybe Text
$sel:streamName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: KinesisStreamingSourceOptions
s@KinesisStreamingSourceOptions' {} Maybe Text
a -> KinesisStreamingSourceOptions
s {$sel:streamName:KinesisStreamingSourceOptions' :: Maybe Text
streamName = Maybe Text
a} :: KinesisStreamingSourceOptions)

instance Data.FromJSON KinesisStreamingSourceOptions where
  parseJSON :: Value -> Parser KinesisStreamingSourceOptions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"KinesisStreamingSourceOptions"
      ( \Object
x ->
          Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe StartingPosition
-> Maybe Text
-> Maybe Text
-> KinesisStreamingSourceOptions
KinesisStreamingSourceOptions'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AddIdleTimeBetweenReads")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AvoidEmptyBatches")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Classification")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Delimiter")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DescribeShardInterval")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"EndpointUrl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IdleTimeBetweenReadsInMs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxFetchRecordsPerShard")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxFetchTimeInMs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxRecordPerRead")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxRetryIntervalMs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NumRetries")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RetryIntervalMs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RoleSessionName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StartingPosition")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StreamArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StreamName")
      )

instance
  Prelude.Hashable
    KinesisStreamingSourceOptions
  where
  hashWithSalt :: Int -> KinesisStreamingSourceOptions -> Int
hashWithSalt Int
_salt KinesisStreamingSourceOptions' {Maybe Bool
Maybe Natural
Maybe Text
Maybe StartingPosition
streamName :: Maybe Text
streamArn :: Maybe Text
startingPosition :: Maybe StartingPosition
roleSessionName :: Maybe Text
roleArn :: Maybe Text
retryIntervalMs :: Maybe Natural
numRetries :: Maybe Natural
maxRetryIntervalMs :: Maybe Natural
maxRecordPerRead :: Maybe Natural
maxFetchTimeInMs :: Maybe Natural
maxFetchRecordsPerShard :: Maybe Natural
idleTimeBetweenReadsInMs :: Maybe Natural
endpointUrl :: Maybe Text
describeShardInterval :: Maybe Natural
delimiter :: Maybe Text
classification :: Maybe Text
avoidEmptyBatches :: Maybe Bool
addIdleTimeBetweenReads :: Maybe Bool
$sel:streamName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:streamArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:startingPosition:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe StartingPosition
$sel:roleSessionName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:roleArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:retryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:numRetries:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:endpointUrl:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:describeShardInterval:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:delimiter:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:classification:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
$sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
addIdleTimeBetweenReads
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
avoidEmptyBatches
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
classification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
delimiter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
describeShardInterval
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endpointUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
idleTimeBetweenReadsInMs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxFetchRecordsPerShard
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxFetchTimeInMs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRecordPerRead
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRetryIntervalMs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
numRetries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
retryIntervalMs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleSessionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StartingPosition
startingPosition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName

instance Prelude.NFData KinesisStreamingSourceOptions where
  rnf :: KinesisStreamingSourceOptions -> ()
rnf KinesisStreamingSourceOptions' {Maybe Bool
Maybe Natural
Maybe Text
Maybe StartingPosition
streamName :: Maybe Text
streamArn :: Maybe Text
startingPosition :: Maybe StartingPosition
roleSessionName :: Maybe Text
roleArn :: Maybe Text
retryIntervalMs :: Maybe Natural
numRetries :: Maybe Natural
maxRetryIntervalMs :: Maybe Natural
maxRecordPerRead :: Maybe Natural
maxFetchTimeInMs :: Maybe Natural
maxFetchRecordsPerShard :: Maybe Natural
idleTimeBetweenReadsInMs :: Maybe Natural
endpointUrl :: Maybe Text
describeShardInterval :: Maybe Natural
delimiter :: Maybe Text
classification :: Maybe Text
avoidEmptyBatches :: Maybe Bool
addIdleTimeBetweenReads :: Maybe Bool
$sel:streamName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:streamArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:startingPosition:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe StartingPosition
$sel:roleSessionName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:roleArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:retryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:numRetries:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:endpointUrl:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:describeShardInterval:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:delimiter:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:classification:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
$sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
addIdleTimeBetweenReads
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
avoidEmptyBatches
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
classification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
delimiter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
describeShardInterval
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
idleTimeBetweenReadsInMs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxFetchRecordsPerShard
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxFetchTimeInMs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRecordPerRead
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRetryIntervalMs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
numRetries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
retryIntervalMs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleSessionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StartingPosition
startingPosition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamName

instance Data.ToJSON KinesisStreamingSourceOptions where
  toJSON :: KinesisStreamingSourceOptions -> Value
toJSON KinesisStreamingSourceOptions' {Maybe Bool
Maybe Natural
Maybe Text
Maybe StartingPosition
streamName :: Maybe Text
streamArn :: Maybe Text
startingPosition :: Maybe StartingPosition
roleSessionName :: Maybe Text
roleArn :: Maybe Text
retryIntervalMs :: Maybe Natural
numRetries :: Maybe Natural
maxRetryIntervalMs :: Maybe Natural
maxRecordPerRead :: Maybe Natural
maxFetchTimeInMs :: Maybe Natural
maxFetchRecordsPerShard :: Maybe Natural
idleTimeBetweenReadsInMs :: Maybe Natural
endpointUrl :: Maybe Text
describeShardInterval :: Maybe Natural
delimiter :: Maybe Text
classification :: Maybe Text
avoidEmptyBatches :: Maybe Bool
addIdleTimeBetweenReads :: Maybe Bool
$sel:streamName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:streamArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:startingPosition:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe StartingPosition
$sel:roleSessionName:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:roleArn:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:retryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:numRetries:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRetryIntervalMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxRecordPerRead:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchTimeInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:maxFetchRecordsPerShard:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:idleTimeBetweenReadsInMs:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:endpointUrl:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:describeShardInterval:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Natural
$sel:delimiter:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:classification:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Text
$sel:avoidEmptyBatches:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
$sel:addIdleTimeBetweenReads:KinesisStreamingSourceOptions' :: KinesisStreamingSourceOptions -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AddIdleTimeBetweenReads" 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
addIdleTimeBetweenReads,
            (Key
"AvoidEmptyBatches" 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
avoidEmptyBatches,
            (Key
"Classification" 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
classification,
            (Key
"Delimiter" 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
delimiter,
            (Key
"DescribeShardInterval" 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
describeShardInterval,
            (Key
"EndpointUrl" 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
endpointUrl,
            (Key
"IdleTimeBetweenReadsInMs" 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
idleTimeBetweenReadsInMs,
            (Key
"MaxFetchRecordsPerShard" 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
maxFetchRecordsPerShard,
            (Key
"MaxFetchTimeInMs" 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
maxFetchTimeInMs,
            (Key
"MaxRecordPerRead" 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
maxRecordPerRead,
            (Key
"MaxRetryIntervalMs" 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
maxRetryIntervalMs,
            (Key
"NumRetries" 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
numRetries,
            (Key
"RetryIntervalMs" 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
retryIntervalMs,
            (Key
"RoleArn" 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
roleArn,
            (Key
"RoleSessionName" 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
roleSessionName,
            (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 StartingPosition
startingPosition,
            (Key
"StreamArn" 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
streamArn,
            (Key
"StreamName" 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
streamName
          ]
      )