{-# 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.DynamoDB.Types.SourceTableFeatureDetails
-- 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.DynamoDB.Types.SourceTableFeatureDetails where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types.AttributeValue
import Amazonka.DynamoDB.Types.GlobalSecondaryIndexInfo
import Amazonka.DynamoDB.Types.LocalSecondaryIndexInfo
import Amazonka.DynamoDB.Types.SSEDescription
import Amazonka.DynamoDB.Types.StreamSpecification
import Amazonka.DynamoDB.Types.TimeToLiveDescription
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude

-- | Contains the details of the features enabled on the table when the
-- backup was created. For example, LSIs, GSIs, streams, TTL.
--
-- /See:/ 'newSourceTableFeatureDetails' smart constructor.
data SourceTableFeatureDetails = SourceTableFeatureDetails'
  { -- | Represents the GSI properties for the table when the backup was created.
    -- It includes the IndexName, KeySchema, Projection, and
    -- ProvisionedThroughput for the GSIs on the table at the time of backup.
    SourceTableFeatureDetails -> Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes :: Prelude.Maybe [GlobalSecondaryIndexInfo],
    -- | Represents the LSI properties for the table when the backup was created.
    -- It includes the IndexName, KeySchema and Projection for the LSIs on the
    -- table at the time of backup.
    SourceTableFeatureDetails -> Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes :: Prelude.Maybe [LocalSecondaryIndexInfo],
    -- | The description of the server-side encryption status on the table when
    -- the backup was created.
    SourceTableFeatureDetails -> Maybe SSEDescription
sSEDescription :: Prelude.Maybe SSEDescription,
    -- | Stream settings on the table when the backup was created.
    SourceTableFeatureDetails -> Maybe StreamSpecification
streamDescription :: Prelude.Maybe StreamSpecification,
    -- | Time to Live settings on the table when the backup was created.
    SourceTableFeatureDetails -> Maybe TimeToLiveDescription
timeToLiveDescription :: Prelude.Maybe TimeToLiveDescription
  }
  deriving (SourceTableFeatureDetails -> SourceTableFeatureDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceTableFeatureDetails -> SourceTableFeatureDetails -> Bool
$c/= :: SourceTableFeatureDetails -> SourceTableFeatureDetails -> Bool
== :: SourceTableFeatureDetails -> SourceTableFeatureDetails -> Bool
$c== :: SourceTableFeatureDetails -> SourceTableFeatureDetails -> Bool
Prelude.Eq, ReadPrec [SourceTableFeatureDetails]
ReadPrec SourceTableFeatureDetails
Int -> ReadS SourceTableFeatureDetails
ReadS [SourceTableFeatureDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SourceTableFeatureDetails]
$creadListPrec :: ReadPrec [SourceTableFeatureDetails]
readPrec :: ReadPrec SourceTableFeatureDetails
$creadPrec :: ReadPrec SourceTableFeatureDetails
readList :: ReadS [SourceTableFeatureDetails]
$creadList :: ReadS [SourceTableFeatureDetails]
readsPrec :: Int -> ReadS SourceTableFeatureDetails
$creadsPrec :: Int -> ReadS SourceTableFeatureDetails
Prelude.Read, Int -> SourceTableFeatureDetails -> ShowS
[SourceTableFeatureDetails] -> ShowS
SourceTableFeatureDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceTableFeatureDetails] -> ShowS
$cshowList :: [SourceTableFeatureDetails] -> ShowS
show :: SourceTableFeatureDetails -> String
$cshow :: SourceTableFeatureDetails -> String
showsPrec :: Int -> SourceTableFeatureDetails -> ShowS
$cshowsPrec :: Int -> SourceTableFeatureDetails -> ShowS
Prelude.Show, forall x.
Rep SourceTableFeatureDetails x -> SourceTableFeatureDetails
forall x.
SourceTableFeatureDetails -> Rep SourceTableFeatureDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SourceTableFeatureDetails x -> SourceTableFeatureDetails
$cfrom :: forall x.
SourceTableFeatureDetails -> Rep SourceTableFeatureDetails x
Prelude.Generic)

-- |
-- Create a value of 'SourceTableFeatureDetails' 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:
--
-- 'globalSecondaryIndexes', 'sourceTableFeatureDetails_globalSecondaryIndexes' - Represents the GSI properties for the table when the backup was created.
-- It includes the IndexName, KeySchema, Projection, and
-- ProvisionedThroughput for the GSIs on the table at the time of backup.
--
-- 'localSecondaryIndexes', 'sourceTableFeatureDetails_localSecondaryIndexes' - Represents the LSI properties for the table when the backup was created.
-- It includes the IndexName, KeySchema and Projection for the LSIs on the
-- table at the time of backup.
--
-- 'sSEDescription', 'sourceTableFeatureDetails_sSEDescription' - The description of the server-side encryption status on the table when
-- the backup was created.
--
-- 'streamDescription', 'sourceTableFeatureDetails_streamDescription' - Stream settings on the table when the backup was created.
--
-- 'timeToLiveDescription', 'sourceTableFeatureDetails_timeToLiveDescription' - Time to Live settings on the table when the backup was created.
newSourceTableFeatureDetails ::
  SourceTableFeatureDetails
newSourceTableFeatureDetails :: SourceTableFeatureDetails
newSourceTableFeatureDetails =
  SourceTableFeatureDetails'
    { $sel:globalSecondaryIndexes:SourceTableFeatureDetails' :: Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:localSecondaryIndexes:SourceTableFeatureDetails' :: Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes = forall a. Maybe a
Prelude.Nothing,
      $sel:sSEDescription:SourceTableFeatureDetails' :: Maybe SSEDescription
sSEDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:streamDescription:SourceTableFeatureDetails' :: Maybe StreamSpecification
streamDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:timeToLiveDescription:SourceTableFeatureDetails' :: Maybe TimeToLiveDescription
timeToLiveDescription = forall a. Maybe a
Prelude.Nothing
    }

-- | Represents the GSI properties for the table when the backup was created.
-- It includes the IndexName, KeySchema, Projection, and
-- ProvisionedThroughput for the GSIs on the table at the time of backup.
sourceTableFeatureDetails_globalSecondaryIndexes :: Lens.Lens' SourceTableFeatureDetails (Prelude.Maybe [GlobalSecondaryIndexInfo])
sourceTableFeatureDetails_globalSecondaryIndexes :: Lens' SourceTableFeatureDetails (Maybe [GlobalSecondaryIndexInfo])
sourceTableFeatureDetails_globalSecondaryIndexes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableFeatureDetails' {Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexInfo]
$sel:globalSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes} -> Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes) (\s :: SourceTableFeatureDetails
s@SourceTableFeatureDetails' {} Maybe [GlobalSecondaryIndexInfo]
a -> SourceTableFeatureDetails
s {$sel:globalSecondaryIndexes:SourceTableFeatureDetails' :: Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes = Maybe [GlobalSecondaryIndexInfo]
a} :: SourceTableFeatureDetails) 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

-- | Represents the LSI properties for the table when the backup was created.
-- It includes the IndexName, KeySchema and Projection for the LSIs on the
-- table at the time of backup.
sourceTableFeatureDetails_localSecondaryIndexes :: Lens.Lens' SourceTableFeatureDetails (Prelude.Maybe [LocalSecondaryIndexInfo])
sourceTableFeatureDetails_localSecondaryIndexes :: Lens' SourceTableFeatureDetails (Maybe [LocalSecondaryIndexInfo])
sourceTableFeatureDetails_localSecondaryIndexes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableFeatureDetails' {Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexInfo]
$sel:localSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes} -> Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes) (\s :: SourceTableFeatureDetails
s@SourceTableFeatureDetails' {} Maybe [LocalSecondaryIndexInfo]
a -> SourceTableFeatureDetails
s {$sel:localSecondaryIndexes:SourceTableFeatureDetails' :: Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes = Maybe [LocalSecondaryIndexInfo]
a} :: SourceTableFeatureDetails) 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 description of the server-side encryption status on the table when
-- the backup was created.
sourceTableFeatureDetails_sSEDescription :: Lens.Lens' SourceTableFeatureDetails (Prelude.Maybe SSEDescription)
sourceTableFeatureDetails_sSEDescription :: Lens' SourceTableFeatureDetails (Maybe SSEDescription)
sourceTableFeatureDetails_sSEDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableFeatureDetails' {Maybe SSEDescription
sSEDescription :: Maybe SSEDescription
$sel:sSEDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe SSEDescription
sSEDescription} -> Maybe SSEDescription
sSEDescription) (\s :: SourceTableFeatureDetails
s@SourceTableFeatureDetails' {} Maybe SSEDescription
a -> SourceTableFeatureDetails
s {$sel:sSEDescription:SourceTableFeatureDetails' :: Maybe SSEDescription
sSEDescription = Maybe SSEDescription
a} :: SourceTableFeatureDetails)

-- | Stream settings on the table when the backup was created.
sourceTableFeatureDetails_streamDescription :: Lens.Lens' SourceTableFeatureDetails (Prelude.Maybe StreamSpecification)
sourceTableFeatureDetails_streamDescription :: Lens' SourceTableFeatureDetails (Maybe StreamSpecification)
sourceTableFeatureDetails_streamDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableFeatureDetails' {Maybe StreamSpecification
streamDescription :: Maybe StreamSpecification
$sel:streamDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe StreamSpecification
streamDescription} -> Maybe StreamSpecification
streamDescription) (\s :: SourceTableFeatureDetails
s@SourceTableFeatureDetails' {} Maybe StreamSpecification
a -> SourceTableFeatureDetails
s {$sel:streamDescription:SourceTableFeatureDetails' :: Maybe StreamSpecification
streamDescription = Maybe StreamSpecification
a} :: SourceTableFeatureDetails)

-- | Time to Live settings on the table when the backup was created.
sourceTableFeatureDetails_timeToLiveDescription :: Lens.Lens' SourceTableFeatureDetails (Prelude.Maybe TimeToLiveDescription)
sourceTableFeatureDetails_timeToLiveDescription :: Lens' SourceTableFeatureDetails (Maybe TimeToLiveDescription)
sourceTableFeatureDetails_timeToLiveDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableFeatureDetails' {Maybe TimeToLiveDescription
timeToLiveDescription :: Maybe TimeToLiveDescription
$sel:timeToLiveDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe TimeToLiveDescription
timeToLiveDescription} -> Maybe TimeToLiveDescription
timeToLiveDescription) (\s :: SourceTableFeatureDetails
s@SourceTableFeatureDetails' {} Maybe TimeToLiveDescription
a -> SourceTableFeatureDetails
s {$sel:timeToLiveDescription:SourceTableFeatureDetails' :: Maybe TimeToLiveDescription
timeToLiveDescription = Maybe TimeToLiveDescription
a} :: SourceTableFeatureDetails)

instance Data.FromJSON SourceTableFeatureDetails where
  parseJSON :: Value -> Parser SourceTableFeatureDetails
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SourceTableFeatureDetails"
      ( \Object
x ->
          Maybe [GlobalSecondaryIndexInfo]
-> Maybe [LocalSecondaryIndexInfo]
-> Maybe SSEDescription
-> Maybe StreamSpecification
-> Maybe TimeToLiveDescription
-> SourceTableFeatureDetails
SourceTableFeatureDetails'
            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
"GlobalSecondaryIndexes"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"LocalSecondaryIndexes"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"SSEDescription")
            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
"StreamDescription")
            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
"TimeToLiveDescription")
      )

instance Prelude.Hashable SourceTableFeatureDetails where
  hashWithSalt :: Int -> SourceTableFeatureDetails -> Int
hashWithSalt Int
_salt SourceTableFeatureDetails' {Maybe [LocalSecondaryIndexInfo]
Maybe [GlobalSecondaryIndexInfo]
Maybe TimeToLiveDescription
Maybe StreamSpecification
Maybe SSEDescription
timeToLiveDescription :: Maybe TimeToLiveDescription
streamDescription :: Maybe StreamSpecification
sSEDescription :: Maybe SSEDescription
localSecondaryIndexes :: Maybe [LocalSecondaryIndexInfo]
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexInfo]
$sel:timeToLiveDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe TimeToLiveDescription
$sel:streamDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe StreamSpecification
$sel:sSEDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe SSEDescription
$sel:localSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [LocalSecondaryIndexInfo]
$sel:globalSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [GlobalSecondaryIndexInfo]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SSEDescription
sSEDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StreamSpecification
streamDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TimeToLiveDescription
timeToLiveDescription

instance Prelude.NFData SourceTableFeatureDetails where
  rnf :: SourceTableFeatureDetails -> ()
rnf SourceTableFeatureDetails' {Maybe [LocalSecondaryIndexInfo]
Maybe [GlobalSecondaryIndexInfo]
Maybe TimeToLiveDescription
Maybe StreamSpecification
Maybe SSEDescription
timeToLiveDescription :: Maybe TimeToLiveDescription
streamDescription :: Maybe StreamSpecification
sSEDescription :: Maybe SSEDescription
localSecondaryIndexes :: Maybe [LocalSecondaryIndexInfo]
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexInfo]
$sel:timeToLiveDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe TimeToLiveDescription
$sel:streamDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe StreamSpecification
$sel:sSEDescription:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe SSEDescription
$sel:localSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [LocalSecondaryIndexInfo]
$sel:globalSecondaryIndexes:SourceTableFeatureDetails' :: SourceTableFeatureDetails -> Maybe [GlobalSecondaryIndexInfo]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [GlobalSecondaryIndexInfo]
globalSecondaryIndexes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LocalSecondaryIndexInfo]
localSecondaryIndexes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SSEDescription
sSEDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StreamSpecification
streamDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TimeToLiveDescription
timeToLiveDescription