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

-- | Represents the properties of a global table.
--
-- /See:/ 'newGlobalTable' smart constructor.
data GlobalTable = GlobalTable'
  { -- | The global table name.
    GlobalTable -> Maybe Text
globalTableName :: Prelude.Maybe Prelude.Text,
    -- | The Regions where the global table has replicas.
    GlobalTable -> Maybe [Replica]
replicationGroup :: Prelude.Maybe [Replica]
  }
  deriving (GlobalTable -> GlobalTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlobalTable -> GlobalTable -> Bool
$c/= :: GlobalTable -> GlobalTable -> Bool
== :: GlobalTable -> GlobalTable -> Bool
$c== :: GlobalTable -> GlobalTable -> Bool
Prelude.Eq, ReadPrec [GlobalTable]
ReadPrec GlobalTable
Int -> ReadS GlobalTable
ReadS [GlobalTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GlobalTable]
$creadListPrec :: ReadPrec [GlobalTable]
readPrec :: ReadPrec GlobalTable
$creadPrec :: ReadPrec GlobalTable
readList :: ReadS [GlobalTable]
$creadList :: ReadS [GlobalTable]
readsPrec :: Int -> ReadS GlobalTable
$creadsPrec :: Int -> ReadS GlobalTable
Prelude.Read, Int -> GlobalTable -> ShowS
[GlobalTable] -> ShowS
GlobalTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GlobalTable] -> ShowS
$cshowList :: [GlobalTable] -> ShowS
show :: GlobalTable -> String
$cshow :: GlobalTable -> String
showsPrec :: Int -> GlobalTable -> ShowS
$cshowsPrec :: Int -> GlobalTable -> ShowS
Prelude.Show, forall x. Rep GlobalTable x -> GlobalTable
forall x. GlobalTable -> Rep GlobalTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GlobalTable x -> GlobalTable
$cfrom :: forall x. GlobalTable -> Rep GlobalTable x
Prelude.Generic)

-- |
-- Create a value of 'GlobalTable' 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:
--
-- 'globalTableName', 'globalTable_globalTableName' - The global table name.
--
-- 'replicationGroup', 'globalTable_replicationGroup' - The Regions where the global table has replicas.
newGlobalTable ::
  GlobalTable
newGlobalTable :: GlobalTable
newGlobalTable =
  GlobalTable'
    { $sel:globalTableName:GlobalTable' :: Maybe Text
globalTableName = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationGroup:GlobalTable' :: Maybe [Replica]
replicationGroup = forall a. Maybe a
Prelude.Nothing
    }

-- | The global table name.
globalTable_globalTableName :: Lens.Lens' GlobalTable (Prelude.Maybe Prelude.Text)
globalTable_globalTableName :: Lens' GlobalTable (Maybe Text)
globalTable_globalTableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GlobalTable' {Maybe Text
globalTableName :: Maybe Text
$sel:globalTableName:GlobalTable' :: GlobalTable -> Maybe Text
globalTableName} -> Maybe Text
globalTableName) (\s :: GlobalTable
s@GlobalTable' {} Maybe Text
a -> GlobalTable
s {$sel:globalTableName:GlobalTable' :: Maybe Text
globalTableName = Maybe Text
a} :: GlobalTable)

-- | The Regions where the global table has replicas.
globalTable_replicationGroup :: Lens.Lens' GlobalTable (Prelude.Maybe [Replica])
globalTable_replicationGroup :: Lens' GlobalTable (Maybe [Replica])
globalTable_replicationGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GlobalTable' {Maybe [Replica]
replicationGroup :: Maybe [Replica]
$sel:replicationGroup:GlobalTable' :: GlobalTable -> Maybe [Replica]
replicationGroup} -> Maybe [Replica]
replicationGroup) (\s :: GlobalTable
s@GlobalTable' {} Maybe [Replica]
a -> GlobalTable
s {$sel:replicationGroup:GlobalTable' :: Maybe [Replica]
replicationGroup = Maybe [Replica]
a} :: GlobalTable) 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

instance Data.FromJSON GlobalTable where
  parseJSON :: Value -> Parser GlobalTable
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"GlobalTable"
      ( \Object
x ->
          Maybe Text -> Maybe [Replica] -> GlobalTable
GlobalTable'
            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
"GlobalTableName")
            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
"ReplicationGroup"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable GlobalTable where
  hashWithSalt :: Int -> GlobalTable -> Int
hashWithSalt Int
_salt GlobalTable' {Maybe [Replica]
Maybe Text
replicationGroup :: Maybe [Replica]
globalTableName :: Maybe Text
$sel:replicationGroup:GlobalTable' :: GlobalTable -> Maybe [Replica]
$sel:globalTableName:GlobalTable' :: GlobalTable -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
globalTableName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Replica]
replicationGroup

instance Prelude.NFData GlobalTable where
  rnf :: GlobalTable -> ()
rnf GlobalTable' {Maybe [Replica]
Maybe Text
replicationGroup :: Maybe [Replica]
globalTableName :: Maybe Text
$sel:replicationGroup:GlobalTable' :: GlobalTable -> Maybe [Replica]
$sel:globalTableName:GlobalTable' :: GlobalTable -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
globalTableName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Replica]
replicationGroup