{-# 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.ExportDescription
-- 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.ExportDescription 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.ExportFormat
import Amazonka.DynamoDB.Types.ExportStatus
import Amazonka.DynamoDB.Types.S3SseAlgorithm
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude

-- | Represents the properties of the exported table.
--
-- /See:/ 'newExportDescription' smart constructor.
data ExportDescription = ExportDescription'
  { -- | The billable size of the table export.
    ExportDescription -> Maybe Natural
billedSizeBytes :: Prelude.Maybe Prelude.Natural,
    -- | The client token that was provided for the export task. A client token
    -- makes calls to @ExportTableToPointInTimeInput@ idempotent, meaning that
    -- multiple identical calls have the same effect as one single call.
    ExportDescription -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The time at which the export task completed.
    ExportDescription -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the table export.
    ExportDescription -> Maybe Text
exportArn :: Prelude.Maybe Prelude.Text,
    -- | The format of the exported data. Valid values for @ExportFormat@ are
    -- @DYNAMODB_JSON@ or @ION@.
    ExportDescription -> Maybe ExportFormat
exportFormat :: Prelude.Maybe ExportFormat,
    -- | The name of the manifest file for the export task.
    ExportDescription -> Maybe Text
exportManifest :: Prelude.Maybe Prelude.Text,
    -- | Export can be in one of the following states: IN_PROGRESS, COMPLETED, or
    -- FAILED.
    ExportDescription -> Maybe ExportStatus
exportStatus :: Prelude.Maybe ExportStatus,
    -- | Point in time from which table data was exported.
    ExportDescription -> Maybe POSIX
exportTime :: Prelude.Maybe Data.POSIX,
    -- | Status code for the result of the failed export.
    ExportDescription -> Maybe Text
failureCode :: Prelude.Maybe Prelude.Text,
    -- | Export failure reason description.
    ExportDescription -> Maybe Text
failureMessage :: Prelude.Maybe Prelude.Text,
    -- | The number of items exported.
    ExportDescription -> Maybe Natural
itemCount :: Prelude.Maybe Prelude.Natural,
    -- | The name of the Amazon S3 bucket containing the export.
    ExportDescription -> Maybe Text
s3Bucket :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that owns the bucket
    -- containing the export.
    ExportDescription -> Maybe Text
s3BucketOwner :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 bucket prefix used as the file name and path of the
    -- exported snapshot.
    ExportDescription -> Maybe Text
s3Prefix :: Prelude.Maybe Prelude.Text,
    -- | Type of encryption used on the bucket where export data is stored. Valid
    -- values for @S3SseAlgorithm@ are:
    --
    -- -   @AES256@ - server-side encryption with Amazon S3 managed keys
    --
    -- -   @KMS@ - server-side encryption with KMS managed keys
    ExportDescription -> Maybe S3SseAlgorithm
s3SseAlgorithm :: Prelude.Maybe S3SseAlgorithm,
    -- | The ID of the KMS managed key used to encrypt the S3 bucket where export
    -- data is stored (if applicable).
    ExportDescription -> Maybe Text
s3SseKmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The time at which the export task began.
    ExportDescription -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the table that was exported.
    ExportDescription -> Maybe Text
tableArn :: Prelude.Maybe Prelude.Text,
    -- | Unique ID of the table that was exported.
    ExportDescription -> Maybe Text
tableId :: Prelude.Maybe Prelude.Text
  }
  deriving (ExportDescription -> ExportDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportDescription -> ExportDescription -> Bool
$c/= :: ExportDescription -> ExportDescription -> Bool
== :: ExportDescription -> ExportDescription -> Bool
$c== :: ExportDescription -> ExportDescription -> Bool
Prelude.Eq, ReadPrec [ExportDescription]
ReadPrec ExportDescription
Int -> ReadS ExportDescription
ReadS [ExportDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportDescription]
$creadListPrec :: ReadPrec [ExportDescription]
readPrec :: ReadPrec ExportDescription
$creadPrec :: ReadPrec ExportDescription
readList :: ReadS [ExportDescription]
$creadList :: ReadS [ExportDescription]
readsPrec :: Int -> ReadS ExportDescription
$creadsPrec :: Int -> ReadS ExportDescription
Prelude.Read, Int -> ExportDescription -> ShowS
[ExportDescription] -> ShowS
ExportDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportDescription] -> ShowS
$cshowList :: [ExportDescription] -> ShowS
show :: ExportDescription -> String
$cshow :: ExportDescription -> String
showsPrec :: Int -> ExportDescription -> ShowS
$cshowsPrec :: Int -> ExportDescription -> ShowS
Prelude.Show, forall x. Rep ExportDescription x -> ExportDescription
forall x. ExportDescription -> Rep ExportDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportDescription x -> ExportDescription
$cfrom :: forall x. ExportDescription -> Rep ExportDescription x
Prelude.Generic)

-- |
-- Create a value of 'ExportDescription' 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:
--
-- 'billedSizeBytes', 'exportDescription_billedSizeBytes' - The billable size of the table export.
--
-- 'clientToken', 'exportDescription_clientToken' - The client token that was provided for the export task. A client token
-- makes calls to @ExportTableToPointInTimeInput@ idempotent, meaning that
-- multiple identical calls have the same effect as one single call.
--
-- 'endTime', 'exportDescription_endTime' - The time at which the export task completed.
--
-- 'exportArn', 'exportDescription_exportArn' - The Amazon Resource Name (ARN) of the table export.
--
-- 'exportFormat', 'exportDescription_exportFormat' - The format of the exported data. Valid values for @ExportFormat@ are
-- @DYNAMODB_JSON@ or @ION@.
--
-- 'exportManifest', 'exportDescription_exportManifest' - The name of the manifest file for the export task.
--
-- 'exportStatus', 'exportDescription_exportStatus' - Export can be in one of the following states: IN_PROGRESS, COMPLETED, or
-- FAILED.
--
-- 'exportTime', 'exportDescription_exportTime' - Point in time from which table data was exported.
--
-- 'failureCode', 'exportDescription_failureCode' - Status code for the result of the failed export.
--
-- 'failureMessage', 'exportDescription_failureMessage' - Export failure reason description.
--
-- 'itemCount', 'exportDescription_itemCount' - The number of items exported.
--
-- 's3Bucket', 'exportDescription_s3Bucket' - The name of the Amazon S3 bucket containing the export.
--
-- 's3BucketOwner', 'exportDescription_s3BucketOwner' - The ID of the Amazon Web Services account that owns the bucket
-- containing the export.
--
-- 's3Prefix', 'exportDescription_s3Prefix' - The Amazon S3 bucket prefix used as the file name and path of the
-- exported snapshot.
--
-- 's3SseAlgorithm', 'exportDescription_s3SseAlgorithm' - Type of encryption used on the bucket where export data is stored. Valid
-- values for @S3SseAlgorithm@ are:
--
-- -   @AES256@ - server-side encryption with Amazon S3 managed keys
--
-- -   @KMS@ - server-side encryption with KMS managed keys
--
-- 's3SseKmsKeyId', 'exportDescription_s3SseKmsKeyId' - The ID of the KMS managed key used to encrypt the S3 bucket where export
-- data is stored (if applicable).
--
-- 'startTime', 'exportDescription_startTime' - The time at which the export task began.
--
-- 'tableArn', 'exportDescription_tableArn' - The Amazon Resource Name (ARN) of the table that was exported.
--
-- 'tableId', 'exportDescription_tableId' - Unique ID of the table that was exported.
newExportDescription ::
  ExportDescription
newExportDescription :: ExportDescription
newExportDescription =
  ExportDescription'
    { $sel:billedSizeBytes:ExportDescription' :: Maybe Natural
billedSizeBytes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clientToken:ExportDescription' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:ExportDescription' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:exportArn:ExportDescription' :: Maybe Text
exportArn = forall a. Maybe a
Prelude.Nothing,
      $sel:exportFormat:ExportDescription' :: Maybe ExportFormat
exportFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:exportManifest:ExportDescription' :: Maybe Text
exportManifest = forall a. Maybe a
Prelude.Nothing,
      $sel:exportStatus:ExportDescription' :: Maybe ExportStatus
exportStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:exportTime:ExportDescription' :: Maybe POSIX
exportTime = forall a. Maybe a
Prelude.Nothing,
      $sel:failureCode:ExportDescription' :: Maybe Text
failureCode = forall a. Maybe a
Prelude.Nothing,
      $sel:failureMessage:ExportDescription' :: Maybe Text
failureMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:itemCount:ExportDescription' :: Maybe Natural
itemCount = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Bucket:ExportDescription' :: Maybe Text
s3Bucket = forall a. Maybe a
Prelude.Nothing,
      $sel:s3BucketOwner:ExportDescription' :: Maybe Text
s3BucketOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Prefix:ExportDescription' :: Maybe Text
s3Prefix = forall a. Maybe a
Prelude.Nothing,
      $sel:s3SseAlgorithm:ExportDescription' :: Maybe S3SseAlgorithm
s3SseAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:s3SseKmsKeyId:ExportDescription' :: Maybe Text
s3SseKmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:ExportDescription' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:tableArn:ExportDescription' :: Maybe Text
tableArn = forall a. Maybe a
Prelude.Nothing,
      $sel:tableId:ExportDescription' :: Maybe Text
tableId = forall a. Maybe a
Prelude.Nothing
    }

-- | The billable size of the table export.
exportDescription_billedSizeBytes :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Natural)
exportDescription_billedSizeBytes :: Lens' ExportDescription (Maybe Natural)
exportDescription_billedSizeBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Natural
billedSizeBytes :: Maybe Natural
$sel:billedSizeBytes:ExportDescription' :: ExportDescription -> Maybe Natural
billedSizeBytes} -> Maybe Natural
billedSizeBytes) (\s :: ExportDescription
s@ExportDescription' {} Maybe Natural
a -> ExportDescription
s {$sel:billedSizeBytes:ExportDescription' :: Maybe Natural
billedSizeBytes = Maybe Natural
a} :: ExportDescription)

-- | The client token that was provided for the export task. A client token
-- makes calls to @ExportTableToPointInTimeInput@ idempotent, meaning that
-- multiple identical calls have the same effect as one single call.
exportDescription_clientToken :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_clientToken :: Lens' ExportDescription (Maybe Text)
exportDescription_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:ExportDescription' :: ExportDescription -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:clientToken:ExportDescription' :: Maybe Text
clientToken = Maybe Text
a} :: ExportDescription)

-- | The time at which the export task completed.
exportDescription_endTime :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.UTCTime)
exportDescription_endTime :: Lens' ExportDescription (Maybe UTCTime)
exportDescription_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:ExportDescription' :: ExportDescription -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: ExportDescription
s@ExportDescription' {} Maybe POSIX
a -> ExportDescription
s {$sel:endTime:ExportDescription' :: Maybe POSIX
endTime = Maybe POSIX
a} :: ExportDescription) 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 Amazon Resource Name (ARN) of the table export.
exportDescription_exportArn :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_exportArn :: Lens' ExportDescription (Maybe Text)
exportDescription_exportArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
exportArn :: Maybe Text
$sel:exportArn:ExportDescription' :: ExportDescription -> Maybe Text
exportArn} -> Maybe Text
exportArn) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:exportArn:ExportDescription' :: Maybe Text
exportArn = Maybe Text
a} :: ExportDescription)

-- | The format of the exported data. Valid values for @ExportFormat@ are
-- @DYNAMODB_JSON@ or @ION@.
exportDescription_exportFormat :: Lens.Lens' ExportDescription (Prelude.Maybe ExportFormat)
exportDescription_exportFormat :: Lens' ExportDescription (Maybe ExportFormat)
exportDescription_exportFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe ExportFormat
exportFormat :: Maybe ExportFormat
$sel:exportFormat:ExportDescription' :: ExportDescription -> Maybe ExportFormat
exportFormat} -> Maybe ExportFormat
exportFormat) (\s :: ExportDescription
s@ExportDescription' {} Maybe ExportFormat
a -> ExportDescription
s {$sel:exportFormat:ExportDescription' :: Maybe ExportFormat
exportFormat = Maybe ExportFormat
a} :: ExportDescription)

-- | The name of the manifest file for the export task.
exportDescription_exportManifest :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_exportManifest :: Lens' ExportDescription (Maybe Text)
exportDescription_exportManifest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
exportManifest :: Maybe Text
$sel:exportManifest:ExportDescription' :: ExportDescription -> Maybe Text
exportManifest} -> Maybe Text
exportManifest) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:exportManifest:ExportDescription' :: Maybe Text
exportManifest = Maybe Text
a} :: ExportDescription)

-- | Export can be in one of the following states: IN_PROGRESS, COMPLETED, or
-- FAILED.
exportDescription_exportStatus :: Lens.Lens' ExportDescription (Prelude.Maybe ExportStatus)
exportDescription_exportStatus :: Lens' ExportDescription (Maybe ExportStatus)
exportDescription_exportStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe ExportStatus
exportStatus :: Maybe ExportStatus
$sel:exportStatus:ExportDescription' :: ExportDescription -> Maybe ExportStatus
exportStatus} -> Maybe ExportStatus
exportStatus) (\s :: ExportDescription
s@ExportDescription' {} Maybe ExportStatus
a -> ExportDescription
s {$sel:exportStatus:ExportDescription' :: Maybe ExportStatus
exportStatus = Maybe ExportStatus
a} :: ExportDescription)

-- | Point in time from which table data was exported.
exportDescription_exportTime :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.UTCTime)
exportDescription_exportTime :: Lens' ExportDescription (Maybe UTCTime)
exportDescription_exportTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe POSIX
exportTime :: Maybe POSIX
$sel:exportTime:ExportDescription' :: ExportDescription -> Maybe POSIX
exportTime} -> Maybe POSIX
exportTime) (\s :: ExportDescription
s@ExportDescription' {} Maybe POSIX
a -> ExportDescription
s {$sel:exportTime:ExportDescription' :: Maybe POSIX
exportTime = Maybe POSIX
a} :: ExportDescription) 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

-- | Status code for the result of the failed export.
exportDescription_failureCode :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_failureCode :: Lens' ExportDescription (Maybe Text)
exportDescription_failureCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
failureCode :: Maybe Text
$sel:failureCode:ExportDescription' :: ExportDescription -> Maybe Text
failureCode} -> Maybe Text
failureCode) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:failureCode:ExportDescription' :: Maybe Text
failureCode = Maybe Text
a} :: ExportDescription)

-- | Export failure reason description.
exportDescription_failureMessage :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_failureMessage :: Lens' ExportDescription (Maybe Text)
exportDescription_failureMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
failureMessage :: Maybe Text
$sel:failureMessage:ExportDescription' :: ExportDescription -> Maybe Text
failureMessage} -> Maybe Text
failureMessage) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:failureMessage:ExportDescription' :: Maybe Text
failureMessage = Maybe Text
a} :: ExportDescription)

-- | The number of items exported.
exportDescription_itemCount :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Natural)
exportDescription_itemCount :: Lens' ExportDescription (Maybe Natural)
exportDescription_itemCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Natural
itemCount :: Maybe Natural
$sel:itemCount:ExportDescription' :: ExportDescription -> Maybe Natural
itemCount} -> Maybe Natural
itemCount) (\s :: ExportDescription
s@ExportDescription' {} Maybe Natural
a -> ExportDescription
s {$sel:itemCount:ExportDescription' :: Maybe Natural
itemCount = Maybe Natural
a} :: ExportDescription)

-- | The name of the Amazon S3 bucket containing the export.
exportDescription_s3Bucket :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_s3Bucket :: Lens' ExportDescription (Maybe Text)
exportDescription_s3Bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
s3Bucket :: Maybe Text
$sel:s3Bucket:ExportDescription' :: ExportDescription -> Maybe Text
s3Bucket} -> Maybe Text
s3Bucket) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:s3Bucket:ExportDescription' :: Maybe Text
s3Bucket = Maybe Text
a} :: ExportDescription)

-- | The ID of the Amazon Web Services account that owns the bucket
-- containing the export.
exportDescription_s3BucketOwner :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_s3BucketOwner :: Lens' ExportDescription (Maybe Text)
exportDescription_s3BucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
s3BucketOwner :: Maybe Text
$sel:s3BucketOwner:ExportDescription' :: ExportDescription -> Maybe Text
s3BucketOwner} -> Maybe Text
s3BucketOwner) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:s3BucketOwner:ExportDescription' :: Maybe Text
s3BucketOwner = Maybe Text
a} :: ExportDescription)

-- | The Amazon S3 bucket prefix used as the file name and path of the
-- exported snapshot.
exportDescription_s3Prefix :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_s3Prefix :: Lens' ExportDescription (Maybe Text)
exportDescription_s3Prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
s3Prefix :: Maybe Text
$sel:s3Prefix:ExportDescription' :: ExportDescription -> Maybe Text
s3Prefix} -> Maybe Text
s3Prefix) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:s3Prefix:ExportDescription' :: Maybe Text
s3Prefix = Maybe Text
a} :: ExportDescription)

-- | Type of encryption used on the bucket where export data is stored. Valid
-- values for @S3SseAlgorithm@ are:
--
-- -   @AES256@ - server-side encryption with Amazon S3 managed keys
--
-- -   @KMS@ - server-side encryption with KMS managed keys
exportDescription_s3SseAlgorithm :: Lens.Lens' ExportDescription (Prelude.Maybe S3SseAlgorithm)
exportDescription_s3SseAlgorithm :: Lens' ExportDescription (Maybe S3SseAlgorithm)
exportDescription_s3SseAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe S3SseAlgorithm
s3SseAlgorithm :: Maybe S3SseAlgorithm
$sel:s3SseAlgorithm:ExportDescription' :: ExportDescription -> Maybe S3SseAlgorithm
s3SseAlgorithm} -> Maybe S3SseAlgorithm
s3SseAlgorithm) (\s :: ExportDescription
s@ExportDescription' {} Maybe S3SseAlgorithm
a -> ExportDescription
s {$sel:s3SseAlgorithm:ExportDescription' :: Maybe S3SseAlgorithm
s3SseAlgorithm = Maybe S3SseAlgorithm
a} :: ExportDescription)

-- | The ID of the KMS managed key used to encrypt the S3 bucket where export
-- data is stored (if applicable).
exportDescription_s3SseKmsKeyId :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_s3SseKmsKeyId :: Lens' ExportDescription (Maybe Text)
exportDescription_s3SseKmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
s3SseKmsKeyId :: Maybe Text
$sel:s3SseKmsKeyId:ExportDescription' :: ExportDescription -> Maybe Text
s3SseKmsKeyId} -> Maybe Text
s3SseKmsKeyId) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:s3SseKmsKeyId:ExportDescription' :: Maybe Text
s3SseKmsKeyId = Maybe Text
a} :: ExportDescription)

-- | The time at which the export task began.
exportDescription_startTime :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.UTCTime)
exportDescription_startTime :: Lens' ExportDescription (Maybe UTCTime)
exportDescription_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:ExportDescription' :: ExportDescription -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: ExportDescription
s@ExportDescription' {} Maybe POSIX
a -> ExportDescription
s {$sel:startTime:ExportDescription' :: Maybe POSIX
startTime = Maybe POSIX
a} :: ExportDescription) 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 Amazon Resource Name (ARN) of the table that was exported.
exportDescription_tableArn :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_tableArn :: Lens' ExportDescription (Maybe Text)
exportDescription_tableArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
tableArn :: Maybe Text
$sel:tableArn:ExportDescription' :: ExportDescription -> Maybe Text
tableArn} -> Maybe Text
tableArn) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:tableArn:ExportDescription' :: Maybe Text
tableArn = Maybe Text
a} :: ExportDescription)

-- | Unique ID of the table that was exported.
exportDescription_tableId :: Lens.Lens' ExportDescription (Prelude.Maybe Prelude.Text)
exportDescription_tableId :: Lens' ExportDescription (Maybe Text)
exportDescription_tableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportDescription' {Maybe Text
tableId :: Maybe Text
$sel:tableId:ExportDescription' :: ExportDescription -> Maybe Text
tableId} -> Maybe Text
tableId) (\s :: ExportDescription
s@ExportDescription' {} Maybe Text
a -> ExportDescription
s {$sel:tableId:ExportDescription' :: Maybe Text
tableId = Maybe Text
a} :: ExportDescription)

instance Data.FromJSON ExportDescription where
  parseJSON :: Value -> Parser ExportDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ExportDescription"
      ( \Object
x ->
          Maybe Natural
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe ExportFormat
-> Maybe Text
-> Maybe ExportStatus
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe S3SseAlgorithm
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> ExportDescription
ExportDescription'
            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
"BilledSizeBytes")
            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
"ClientToken")
            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
"EndTime")
            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
"ExportArn")
            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
"ExportFormat")
            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
"ExportManifest")
            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
"ExportStatus")
            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
"ExportTime")
            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
"FailureCode")
            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
"FailureMessage")
            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
"ItemCount")
            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
"S3Bucket")
            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
"S3BucketOwner")
            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
"S3Prefix")
            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
"S3SseAlgorithm")
            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
"S3SseKmsKeyId")
            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
"StartTime")
            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
"TableArn")
            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
"TableId")
      )

instance Prelude.Hashable ExportDescription where
  hashWithSalt :: Int -> ExportDescription -> Int
hashWithSalt Int
_salt ExportDescription' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe S3SseAlgorithm
Maybe ExportStatus
Maybe ExportFormat
tableId :: Maybe Text
tableArn :: Maybe Text
startTime :: Maybe POSIX
s3SseKmsKeyId :: Maybe Text
s3SseAlgorithm :: Maybe S3SseAlgorithm
s3Prefix :: Maybe Text
s3BucketOwner :: Maybe Text
s3Bucket :: Maybe Text
itemCount :: Maybe Natural
failureMessage :: Maybe Text
failureCode :: Maybe Text
exportTime :: Maybe POSIX
exportStatus :: Maybe ExportStatus
exportManifest :: Maybe Text
exportFormat :: Maybe ExportFormat
exportArn :: Maybe Text
endTime :: Maybe POSIX
clientToken :: Maybe Text
billedSizeBytes :: Maybe Natural
$sel:tableId:ExportDescription' :: ExportDescription -> Maybe Text
$sel:tableArn:ExportDescription' :: ExportDescription -> Maybe Text
$sel:startTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:s3SseKmsKeyId:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3SseAlgorithm:ExportDescription' :: ExportDescription -> Maybe S3SseAlgorithm
$sel:s3Prefix:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3BucketOwner:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3Bucket:ExportDescription' :: ExportDescription -> Maybe Text
$sel:itemCount:ExportDescription' :: ExportDescription -> Maybe Natural
$sel:failureMessage:ExportDescription' :: ExportDescription -> Maybe Text
$sel:failureCode:ExportDescription' :: ExportDescription -> Maybe Text
$sel:exportTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:exportStatus:ExportDescription' :: ExportDescription -> Maybe ExportStatus
$sel:exportManifest:ExportDescription' :: ExportDescription -> Maybe Text
$sel:exportFormat:ExportDescription' :: ExportDescription -> Maybe ExportFormat
$sel:exportArn:ExportDescription' :: ExportDescription -> Maybe Text
$sel:endTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:clientToken:ExportDescription' :: ExportDescription -> Maybe Text
$sel:billedSizeBytes:ExportDescription' :: ExportDescription -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
billedSizeBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exportArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExportFormat
exportFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exportManifest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExportStatus
exportStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
exportTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
itemCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3BucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3SseAlgorithm
s3SseAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3SseKmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableId

instance Prelude.NFData ExportDescription where
  rnf :: ExportDescription -> ()
rnf ExportDescription' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe S3SseAlgorithm
Maybe ExportStatus
Maybe ExportFormat
tableId :: Maybe Text
tableArn :: Maybe Text
startTime :: Maybe POSIX
s3SseKmsKeyId :: Maybe Text
s3SseAlgorithm :: Maybe S3SseAlgorithm
s3Prefix :: Maybe Text
s3BucketOwner :: Maybe Text
s3Bucket :: Maybe Text
itemCount :: Maybe Natural
failureMessage :: Maybe Text
failureCode :: Maybe Text
exportTime :: Maybe POSIX
exportStatus :: Maybe ExportStatus
exportManifest :: Maybe Text
exportFormat :: Maybe ExportFormat
exportArn :: Maybe Text
endTime :: Maybe POSIX
clientToken :: Maybe Text
billedSizeBytes :: Maybe Natural
$sel:tableId:ExportDescription' :: ExportDescription -> Maybe Text
$sel:tableArn:ExportDescription' :: ExportDescription -> Maybe Text
$sel:startTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:s3SseKmsKeyId:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3SseAlgorithm:ExportDescription' :: ExportDescription -> Maybe S3SseAlgorithm
$sel:s3Prefix:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3BucketOwner:ExportDescription' :: ExportDescription -> Maybe Text
$sel:s3Bucket:ExportDescription' :: ExportDescription -> Maybe Text
$sel:itemCount:ExportDescription' :: ExportDescription -> Maybe Natural
$sel:failureMessage:ExportDescription' :: ExportDescription -> Maybe Text
$sel:failureCode:ExportDescription' :: ExportDescription -> Maybe Text
$sel:exportTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:exportStatus:ExportDescription' :: ExportDescription -> Maybe ExportStatus
$sel:exportManifest:ExportDescription' :: ExportDescription -> Maybe Text
$sel:exportFormat:ExportDescription' :: ExportDescription -> Maybe ExportFormat
$sel:exportArn:ExportDescription' :: ExportDescription -> Maybe Text
$sel:endTime:ExportDescription' :: ExportDescription -> Maybe POSIX
$sel:clientToken:ExportDescription' :: ExportDescription -> Maybe Text
$sel:billedSizeBytes:ExportDescription' :: ExportDescription -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
billedSizeBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exportArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExportFormat
exportFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exportManifest
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExportStatus
exportStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
exportTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
itemCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3Bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3BucketOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3Prefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3SseAlgorithm
s3SseAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3SseKmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableId