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

-- | Summary information about an export task.
--
-- /See:/ 'newExportSummary' smart constructor.
data ExportSummary = ExportSummary'
  { -- | The Amazon Resource Name (ARN) of the export.
    ExportSummary -> Maybe Text
exportArn :: Prelude.Maybe Prelude.Text,
    -- | Export can be in one of the following states: IN_PROGRESS, COMPLETED, or
    -- FAILED.
    ExportSummary -> Maybe ExportStatus
exportStatus :: Prelude.Maybe ExportStatus
  }
  deriving (ExportSummary -> ExportSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportSummary -> ExportSummary -> Bool
$c/= :: ExportSummary -> ExportSummary -> Bool
== :: ExportSummary -> ExportSummary -> Bool
$c== :: ExportSummary -> ExportSummary -> Bool
Prelude.Eq, ReadPrec [ExportSummary]
ReadPrec ExportSummary
Int -> ReadS ExportSummary
ReadS [ExportSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportSummary]
$creadListPrec :: ReadPrec [ExportSummary]
readPrec :: ReadPrec ExportSummary
$creadPrec :: ReadPrec ExportSummary
readList :: ReadS [ExportSummary]
$creadList :: ReadS [ExportSummary]
readsPrec :: Int -> ReadS ExportSummary
$creadsPrec :: Int -> ReadS ExportSummary
Prelude.Read, Int -> ExportSummary -> ShowS
[ExportSummary] -> ShowS
ExportSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportSummary] -> ShowS
$cshowList :: [ExportSummary] -> ShowS
show :: ExportSummary -> String
$cshow :: ExportSummary -> String
showsPrec :: Int -> ExportSummary -> ShowS
$cshowsPrec :: Int -> ExportSummary -> ShowS
Prelude.Show, forall x. Rep ExportSummary x -> ExportSummary
forall x. ExportSummary -> Rep ExportSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportSummary x -> ExportSummary
$cfrom :: forall x. ExportSummary -> Rep ExportSummary x
Prelude.Generic)

-- |
-- Create a value of 'ExportSummary' 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:
--
-- 'exportArn', 'exportSummary_exportArn' - The Amazon Resource Name (ARN) of the export.
--
-- 'exportStatus', 'exportSummary_exportStatus' - Export can be in one of the following states: IN_PROGRESS, COMPLETED, or
-- FAILED.
newExportSummary ::
  ExportSummary
newExportSummary :: ExportSummary
newExportSummary =
  ExportSummary'
    { $sel:exportArn:ExportSummary' :: Maybe Text
exportArn = forall a. Maybe a
Prelude.Nothing,
      $sel:exportStatus:ExportSummary' :: Maybe ExportStatus
exportStatus = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the export.
exportSummary_exportArn :: Lens.Lens' ExportSummary (Prelude.Maybe Prelude.Text)
exportSummary_exportArn :: Lens' ExportSummary (Maybe Text)
exportSummary_exportArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportSummary' {Maybe Text
exportArn :: Maybe Text
$sel:exportArn:ExportSummary' :: ExportSummary -> Maybe Text
exportArn} -> Maybe Text
exportArn) (\s :: ExportSummary
s@ExportSummary' {} Maybe Text
a -> ExportSummary
s {$sel:exportArn:ExportSummary' :: Maybe Text
exportArn = Maybe Text
a} :: ExportSummary)

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

instance Data.FromJSON ExportSummary where
  parseJSON :: Value -> Parser ExportSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ExportSummary"
      ( \Object
x ->
          Maybe Text -> Maybe ExportStatus -> ExportSummary
ExportSummary'
            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
"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
"ExportStatus")
      )

instance Prelude.Hashable ExportSummary where
  hashWithSalt :: Int -> ExportSummary -> Int
hashWithSalt Int
_salt ExportSummary' {Maybe Text
Maybe ExportStatus
exportStatus :: Maybe ExportStatus
exportArn :: Maybe Text
$sel:exportStatus:ExportSummary' :: ExportSummary -> Maybe ExportStatus
$sel:exportArn:ExportSummary' :: ExportSummary -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exportArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExportStatus
exportStatus

instance Prelude.NFData ExportSummary where
  rnf :: ExportSummary -> ()
rnf ExportSummary' {Maybe Text
Maybe ExportStatus
exportStatus :: Maybe ExportStatus
exportArn :: Maybe Text
$sel:exportStatus:ExportSummary' :: ExportSummary -> Maybe ExportStatus
$sel:exportArn:ExportSummary' :: ExportSummary -> Maybe Text
..} =
    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 ExportStatus
exportStatus