{-# 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.KinesisAnalyticsV2.Types.CheckpointConfigurationDescription
-- 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.KinesisAnalyticsV2.Types.CheckpointConfigurationDescription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisAnalyticsV2.Types.ConfigurationType
import qualified Amazonka.Prelude as Prelude

-- | Describes checkpointing parameters for a Flink-based Kinesis Data
-- Analytics application.
--
-- /See:/ 'newCheckpointConfigurationDescription' smart constructor.
data CheckpointConfigurationDescription = CheckpointConfigurationDescription'
  { -- | Describes the interval in milliseconds between checkpoint operations.
    --
    -- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
    -- application will use a @CheckpointInterval@ value of 60000, even if this
    -- value is set to another value using this API or in application code.
    CheckpointConfigurationDescription -> Maybe Natural
checkpointInterval :: Prelude.Maybe Prelude.Natural,
    -- | Describes whether checkpointing is enabled for a Flink-based Kinesis
    -- Data Analytics application.
    --
    -- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
    -- application will use a @CheckpointingEnabled@ value of @true@, even if
    -- this value is set to another value using this API or in application
    -- code.
    CheckpointConfigurationDescription -> Maybe Bool
checkpointingEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Describes whether the application uses the default checkpointing
    -- behavior in Kinesis Data Analytics.
    --
    -- If this value is set to @DEFAULT@, the application will use the
    -- following values, even if they are set to other values using APIs or
    -- application code:
    --
    -- -   __CheckpointingEnabled:__ true
    --
    -- -   __CheckpointInterval:__ 60000
    --
    -- -   __MinPauseBetweenCheckpoints:__ 5000
    CheckpointConfigurationDescription -> Maybe ConfigurationType
configurationType :: Prelude.Maybe ConfigurationType,
    -- | Describes the minimum time in milliseconds after a checkpoint operation
    -- completes that a new checkpoint operation can start.
    --
    -- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
    -- application will use a @MinPauseBetweenCheckpoints@ value of 5000, even
    -- if this value is set using this API or in application code.
    CheckpointConfigurationDescription -> Maybe Natural
minPauseBetweenCheckpoints :: Prelude.Maybe Prelude.Natural
  }
  deriving (CheckpointConfigurationDescription
-> CheckpointConfigurationDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckpointConfigurationDescription
-> CheckpointConfigurationDescription -> Bool
$c/= :: CheckpointConfigurationDescription
-> CheckpointConfigurationDescription -> Bool
== :: CheckpointConfigurationDescription
-> CheckpointConfigurationDescription -> Bool
$c== :: CheckpointConfigurationDescription
-> CheckpointConfigurationDescription -> Bool
Prelude.Eq, ReadPrec [CheckpointConfigurationDescription]
ReadPrec CheckpointConfigurationDescription
Int -> ReadS CheckpointConfigurationDescription
ReadS [CheckpointConfigurationDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CheckpointConfigurationDescription]
$creadListPrec :: ReadPrec [CheckpointConfigurationDescription]
readPrec :: ReadPrec CheckpointConfigurationDescription
$creadPrec :: ReadPrec CheckpointConfigurationDescription
readList :: ReadS [CheckpointConfigurationDescription]
$creadList :: ReadS [CheckpointConfigurationDescription]
readsPrec :: Int -> ReadS CheckpointConfigurationDescription
$creadsPrec :: Int -> ReadS CheckpointConfigurationDescription
Prelude.Read, Int -> CheckpointConfigurationDescription -> ShowS
[CheckpointConfigurationDescription] -> ShowS
CheckpointConfigurationDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckpointConfigurationDescription] -> ShowS
$cshowList :: [CheckpointConfigurationDescription] -> ShowS
show :: CheckpointConfigurationDescription -> String
$cshow :: CheckpointConfigurationDescription -> String
showsPrec :: Int -> CheckpointConfigurationDescription -> ShowS
$cshowsPrec :: Int -> CheckpointConfigurationDescription -> ShowS
Prelude.Show, forall x.
Rep CheckpointConfigurationDescription x
-> CheckpointConfigurationDescription
forall x.
CheckpointConfigurationDescription
-> Rep CheckpointConfigurationDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckpointConfigurationDescription x
-> CheckpointConfigurationDescription
$cfrom :: forall x.
CheckpointConfigurationDescription
-> Rep CheckpointConfigurationDescription x
Prelude.Generic)

-- |
-- Create a value of 'CheckpointConfigurationDescription' 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:
--
-- 'checkpointInterval', 'checkpointConfigurationDescription_checkpointInterval' - Describes the interval in milliseconds between checkpoint operations.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @CheckpointInterval@ value of 60000, even if this
-- value is set to another value using this API or in application code.
--
-- 'checkpointingEnabled', 'checkpointConfigurationDescription_checkpointingEnabled' - Describes whether checkpointing is enabled for a Flink-based Kinesis
-- Data Analytics application.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @CheckpointingEnabled@ value of @true@, even if
-- this value is set to another value using this API or in application
-- code.
--
-- 'configurationType', 'checkpointConfigurationDescription_configurationType' - Describes whether the application uses the default checkpointing
-- behavior in Kinesis Data Analytics.
--
-- If this value is set to @DEFAULT@, the application will use the
-- following values, even if they are set to other values using APIs or
-- application code:
--
-- -   __CheckpointingEnabled:__ true
--
-- -   __CheckpointInterval:__ 60000
--
-- -   __MinPauseBetweenCheckpoints:__ 5000
--
-- 'minPauseBetweenCheckpoints', 'checkpointConfigurationDescription_minPauseBetweenCheckpoints' - Describes the minimum time in milliseconds after a checkpoint operation
-- completes that a new checkpoint operation can start.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @MinPauseBetweenCheckpoints@ value of 5000, even
-- if this value is set using this API or in application code.
newCheckpointConfigurationDescription ::
  CheckpointConfigurationDescription
newCheckpointConfigurationDescription :: CheckpointConfigurationDescription
newCheckpointConfigurationDescription =
  CheckpointConfigurationDescription'
    { $sel:checkpointInterval:CheckpointConfigurationDescription' :: Maybe Natural
checkpointInterval =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checkpointingEnabled:CheckpointConfigurationDescription' :: Maybe Bool
checkpointingEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationType:CheckpointConfigurationDescription' :: Maybe ConfigurationType
configurationType = forall a. Maybe a
Prelude.Nothing,
      $sel:minPauseBetweenCheckpoints:CheckpointConfigurationDescription' :: Maybe Natural
minPauseBetweenCheckpoints =
        forall a. Maybe a
Prelude.Nothing
    }

-- | Describes the interval in milliseconds between checkpoint operations.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @CheckpointInterval@ value of 60000, even if this
-- value is set to another value using this API or in application code.
checkpointConfigurationDescription_checkpointInterval :: Lens.Lens' CheckpointConfigurationDescription (Prelude.Maybe Prelude.Natural)
checkpointConfigurationDescription_checkpointInterval :: Lens' CheckpointConfigurationDescription (Maybe Natural)
checkpointConfigurationDescription_checkpointInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckpointConfigurationDescription' {Maybe Natural
checkpointInterval :: Maybe Natural
$sel:checkpointInterval:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
checkpointInterval} -> Maybe Natural
checkpointInterval) (\s :: CheckpointConfigurationDescription
s@CheckpointConfigurationDescription' {} Maybe Natural
a -> CheckpointConfigurationDescription
s {$sel:checkpointInterval:CheckpointConfigurationDescription' :: Maybe Natural
checkpointInterval = Maybe Natural
a} :: CheckpointConfigurationDescription)

-- | Describes whether checkpointing is enabled for a Flink-based Kinesis
-- Data Analytics application.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @CheckpointingEnabled@ value of @true@, even if
-- this value is set to another value using this API or in application
-- code.
checkpointConfigurationDescription_checkpointingEnabled :: Lens.Lens' CheckpointConfigurationDescription (Prelude.Maybe Prelude.Bool)
checkpointConfigurationDescription_checkpointingEnabled :: Lens' CheckpointConfigurationDescription (Maybe Bool)
checkpointConfigurationDescription_checkpointingEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckpointConfigurationDescription' {Maybe Bool
checkpointingEnabled :: Maybe Bool
$sel:checkpointingEnabled:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Bool
checkpointingEnabled} -> Maybe Bool
checkpointingEnabled) (\s :: CheckpointConfigurationDescription
s@CheckpointConfigurationDescription' {} Maybe Bool
a -> CheckpointConfigurationDescription
s {$sel:checkpointingEnabled:CheckpointConfigurationDescription' :: Maybe Bool
checkpointingEnabled = Maybe Bool
a} :: CheckpointConfigurationDescription)

-- | Describes whether the application uses the default checkpointing
-- behavior in Kinesis Data Analytics.
--
-- If this value is set to @DEFAULT@, the application will use the
-- following values, even if they are set to other values using APIs or
-- application code:
--
-- -   __CheckpointingEnabled:__ true
--
-- -   __CheckpointInterval:__ 60000
--
-- -   __MinPauseBetweenCheckpoints:__ 5000
checkpointConfigurationDescription_configurationType :: Lens.Lens' CheckpointConfigurationDescription (Prelude.Maybe ConfigurationType)
checkpointConfigurationDescription_configurationType :: Lens' CheckpointConfigurationDescription (Maybe ConfigurationType)
checkpointConfigurationDescription_configurationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckpointConfigurationDescription' {Maybe ConfigurationType
configurationType :: Maybe ConfigurationType
$sel:configurationType:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe ConfigurationType
configurationType} -> Maybe ConfigurationType
configurationType) (\s :: CheckpointConfigurationDescription
s@CheckpointConfigurationDescription' {} Maybe ConfigurationType
a -> CheckpointConfigurationDescription
s {$sel:configurationType:CheckpointConfigurationDescription' :: Maybe ConfigurationType
configurationType = Maybe ConfigurationType
a} :: CheckpointConfigurationDescription)

-- | Describes the minimum time in milliseconds after a checkpoint operation
-- completes that a new checkpoint operation can start.
--
-- If @CheckpointConfiguration.ConfigurationType@ is @DEFAULT@, the
-- application will use a @MinPauseBetweenCheckpoints@ value of 5000, even
-- if this value is set using this API or in application code.
checkpointConfigurationDescription_minPauseBetweenCheckpoints :: Lens.Lens' CheckpointConfigurationDescription (Prelude.Maybe Prelude.Natural)
checkpointConfigurationDescription_minPauseBetweenCheckpoints :: Lens' CheckpointConfigurationDescription (Maybe Natural)
checkpointConfigurationDescription_minPauseBetweenCheckpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckpointConfigurationDescription' {Maybe Natural
minPauseBetweenCheckpoints :: Maybe Natural
$sel:minPauseBetweenCheckpoints:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
minPauseBetweenCheckpoints} -> Maybe Natural
minPauseBetweenCheckpoints) (\s :: CheckpointConfigurationDescription
s@CheckpointConfigurationDescription' {} Maybe Natural
a -> CheckpointConfigurationDescription
s {$sel:minPauseBetweenCheckpoints:CheckpointConfigurationDescription' :: Maybe Natural
minPauseBetweenCheckpoints = Maybe Natural
a} :: CheckpointConfigurationDescription)

instance
  Data.FromJSON
    CheckpointConfigurationDescription
  where
  parseJSON :: Value -> Parser CheckpointConfigurationDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CheckpointConfigurationDescription"
      ( \Object
x ->
          Maybe Natural
-> Maybe Bool
-> Maybe ConfigurationType
-> Maybe Natural
-> CheckpointConfigurationDescription
CheckpointConfigurationDescription'
            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
"CheckpointInterval")
            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
"CheckpointingEnabled")
            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
"ConfigurationType")
            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
"MinPauseBetweenCheckpoints")
      )

instance
  Prelude.Hashable
    CheckpointConfigurationDescription
  where
  hashWithSalt :: Int -> CheckpointConfigurationDescription -> Int
hashWithSalt
    Int
_salt
    CheckpointConfigurationDescription' {Maybe Bool
Maybe Natural
Maybe ConfigurationType
minPauseBetweenCheckpoints :: Maybe Natural
configurationType :: Maybe ConfigurationType
checkpointingEnabled :: Maybe Bool
checkpointInterval :: Maybe Natural
$sel:minPauseBetweenCheckpoints:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
$sel:configurationType:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe ConfigurationType
$sel:checkpointingEnabled:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Bool
$sel:checkpointInterval:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
checkpointInterval
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
checkpointingEnabled
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConfigurationType
configurationType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
minPauseBetweenCheckpoints

instance
  Prelude.NFData
    CheckpointConfigurationDescription
  where
  rnf :: CheckpointConfigurationDescription -> ()
rnf CheckpointConfigurationDescription' {Maybe Bool
Maybe Natural
Maybe ConfigurationType
minPauseBetweenCheckpoints :: Maybe Natural
configurationType :: Maybe ConfigurationType
checkpointingEnabled :: Maybe Bool
checkpointInterval :: Maybe Natural
$sel:minPauseBetweenCheckpoints:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
$sel:configurationType:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe ConfigurationType
$sel:checkpointingEnabled:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Bool
$sel:checkpointInterval:CheckpointConfigurationDescription' :: CheckpointConfigurationDescription -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
checkpointInterval
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
checkpointingEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfigurationType
configurationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
minPauseBetweenCheckpoints