{-# 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.ElastiCache.Types.NodeGroup
-- 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.ElastiCache.Types.NodeGroup where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElastiCache.Types.Endpoint
import Amazonka.ElastiCache.Types.NodeGroupMember
import qualified Amazonka.Prelude as Prelude

-- | Represents a collection of cache nodes in a replication group. One node
-- in the node group is the read\/write primary node. All the other nodes
-- are read-only Replica nodes.
--
-- /See:/ 'newNodeGroup' smart constructor.
data NodeGroup = NodeGroup'
  { -- | The identifier for the node group (shard). A Redis (cluster mode
    -- disabled) replication group contains only 1 node group; therefore, the
    -- node group ID is 0001. A Redis (cluster mode enabled) replication group
    -- contains 1 to 90 node groups numbered 0001 to 0090. Optionally, the user
    -- can provide the id for a node group.
    NodeGroup -> Maybe Text
nodeGroupId :: Prelude.Maybe Prelude.Text,
    -- | A list containing information about individual nodes within the node
    -- group (shard).
    NodeGroup -> Maybe [NodeGroupMember]
nodeGroupMembers :: Prelude.Maybe [NodeGroupMember],
    -- | The endpoint of the primary node in this node group (shard).
    NodeGroup -> Maybe Endpoint
primaryEndpoint :: Prelude.Maybe Endpoint,
    -- | The endpoint of the replica nodes in this node group (shard).
    NodeGroup -> Maybe Endpoint
readerEndpoint :: Prelude.Maybe Endpoint,
    -- | The keyspace for this node group (shard).
    NodeGroup -> Maybe Text
slots :: Prelude.Maybe Prelude.Text,
    -- | The current state of this replication group - @creating@, @available@,
    -- @modifying@, @deleting@.
    NodeGroup -> Maybe Text
status :: Prelude.Maybe Prelude.Text
  }
  deriving (NodeGroup -> NodeGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeGroup -> NodeGroup -> Bool
$c/= :: NodeGroup -> NodeGroup -> Bool
== :: NodeGroup -> NodeGroup -> Bool
$c== :: NodeGroup -> NodeGroup -> Bool
Prelude.Eq, ReadPrec [NodeGroup]
ReadPrec NodeGroup
Int -> ReadS NodeGroup
ReadS [NodeGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NodeGroup]
$creadListPrec :: ReadPrec [NodeGroup]
readPrec :: ReadPrec NodeGroup
$creadPrec :: ReadPrec NodeGroup
readList :: ReadS [NodeGroup]
$creadList :: ReadS [NodeGroup]
readsPrec :: Int -> ReadS NodeGroup
$creadsPrec :: Int -> ReadS NodeGroup
Prelude.Read, Int -> NodeGroup -> ShowS
[NodeGroup] -> ShowS
NodeGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeGroup] -> ShowS
$cshowList :: [NodeGroup] -> ShowS
show :: NodeGroup -> String
$cshow :: NodeGroup -> String
showsPrec :: Int -> NodeGroup -> ShowS
$cshowsPrec :: Int -> NodeGroup -> ShowS
Prelude.Show, forall x. Rep NodeGroup x -> NodeGroup
forall x. NodeGroup -> Rep NodeGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NodeGroup x -> NodeGroup
$cfrom :: forall x. NodeGroup -> Rep NodeGroup x
Prelude.Generic)

-- |
-- Create a value of 'NodeGroup' 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:
--
-- 'nodeGroupId', 'nodeGroup_nodeGroupId' - The identifier for the node group (shard). A Redis (cluster mode
-- disabled) replication group contains only 1 node group; therefore, the
-- node group ID is 0001. A Redis (cluster mode enabled) replication group
-- contains 1 to 90 node groups numbered 0001 to 0090. Optionally, the user
-- can provide the id for a node group.
--
-- 'nodeGroupMembers', 'nodeGroup_nodeGroupMembers' - A list containing information about individual nodes within the node
-- group (shard).
--
-- 'primaryEndpoint', 'nodeGroup_primaryEndpoint' - The endpoint of the primary node in this node group (shard).
--
-- 'readerEndpoint', 'nodeGroup_readerEndpoint' - The endpoint of the replica nodes in this node group (shard).
--
-- 'slots', 'nodeGroup_slots' - The keyspace for this node group (shard).
--
-- 'status', 'nodeGroup_status' - The current state of this replication group - @creating@, @available@,
-- @modifying@, @deleting@.
newNodeGroup ::
  NodeGroup
newNodeGroup :: NodeGroup
newNodeGroup =
  NodeGroup'
    { $sel:nodeGroupId:NodeGroup' :: Maybe Text
nodeGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:nodeGroupMembers:NodeGroup' :: Maybe [NodeGroupMember]
nodeGroupMembers = forall a. Maybe a
Prelude.Nothing,
      $sel:primaryEndpoint:NodeGroup' :: Maybe Endpoint
primaryEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:readerEndpoint:NodeGroup' :: Maybe Endpoint
readerEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:slots:NodeGroup' :: Maybe Text
slots = forall a. Maybe a
Prelude.Nothing,
      $sel:status:NodeGroup' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The identifier for the node group (shard). A Redis (cluster mode
-- disabled) replication group contains only 1 node group; therefore, the
-- node group ID is 0001. A Redis (cluster mode enabled) replication group
-- contains 1 to 90 node groups numbered 0001 to 0090. Optionally, the user
-- can provide the id for a node group.
nodeGroup_nodeGroupId :: Lens.Lens' NodeGroup (Prelude.Maybe Prelude.Text)
nodeGroup_nodeGroupId :: Lens' NodeGroup (Maybe Text)
nodeGroup_nodeGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe Text
nodeGroupId :: Maybe Text
$sel:nodeGroupId:NodeGroup' :: NodeGroup -> Maybe Text
nodeGroupId} -> Maybe Text
nodeGroupId) (\s :: NodeGroup
s@NodeGroup' {} Maybe Text
a -> NodeGroup
s {$sel:nodeGroupId:NodeGroup' :: Maybe Text
nodeGroupId = Maybe Text
a} :: NodeGroup)

-- | A list containing information about individual nodes within the node
-- group (shard).
nodeGroup_nodeGroupMembers :: Lens.Lens' NodeGroup (Prelude.Maybe [NodeGroupMember])
nodeGroup_nodeGroupMembers :: Lens' NodeGroup (Maybe [NodeGroupMember])
nodeGroup_nodeGroupMembers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe [NodeGroupMember]
nodeGroupMembers :: Maybe [NodeGroupMember]
$sel:nodeGroupMembers:NodeGroup' :: NodeGroup -> Maybe [NodeGroupMember]
nodeGroupMembers} -> Maybe [NodeGroupMember]
nodeGroupMembers) (\s :: NodeGroup
s@NodeGroup' {} Maybe [NodeGroupMember]
a -> NodeGroup
s {$sel:nodeGroupMembers:NodeGroup' :: Maybe [NodeGroupMember]
nodeGroupMembers = Maybe [NodeGroupMember]
a} :: NodeGroup) 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 endpoint of the primary node in this node group (shard).
nodeGroup_primaryEndpoint :: Lens.Lens' NodeGroup (Prelude.Maybe Endpoint)
nodeGroup_primaryEndpoint :: Lens' NodeGroup (Maybe Endpoint)
nodeGroup_primaryEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe Endpoint
primaryEndpoint :: Maybe Endpoint
$sel:primaryEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
primaryEndpoint} -> Maybe Endpoint
primaryEndpoint) (\s :: NodeGroup
s@NodeGroup' {} Maybe Endpoint
a -> NodeGroup
s {$sel:primaryEndpoint:NodeGroup' :: Maybe Endpoint
primaryEndpoint = Maybe Endpoint
a} :: NodeGroup)

-- | The endpoint of the replica nodes in this node group (shard).
nodeGroup_readerEndpoint :: Lens.Lens' NodeGroup (Prelude.Maybe Endpoint)
nodeGroup_readerEndpoint :: Lens' NodeGroup (Maybe Endpoint)
nodeGroup_readerEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe Endpoint
readerEndpoint :: Maybe Endpoint
$sel:readerEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
readerEndpoint} -> Maybe Endpoint
readerEndpoint) (\s :: NodeGroup
s@NodeGroup' {} Maybe Endpoint
a -> NodeGroup
s {$sel:readerEndpoint:NodeGroup' :: Maybe Endpoint
readerEndpoint = Maybe Endpoint
a} :: NodeGroup)

-- | The keyspace for this node group (shard).
nodeGroup_slots :: Lens.Lens' NodeGroup (Prelude.Maybe Prelude.Text)
nodeGroup_slots :: Lens' NodeGroup (Maybe Text)
nodeGroup_slots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe Text
slots :: Maybe Text
$sel:slots:NodeGroup' :: NodeGroup -> Maybe Text
slots} -> Maybe Text
slots) (\s :: NodeGroup
s@NodeGroup' {} Maybe Text
a -> NodeGroup
s {$sel:slots:NodeGroup' :: Maybe Text
slots = Maybe Text
a} :: NodeGroup)

-- | The current state of this replication group - @creating@, @available@,
-- @modifying@, @deleting@.
nodeGroup_status :: Lens.Lens' NodeGroup (Prelude.Maybe Prelude.Text)
nodeGroup_status :: Lens' NodeGroup (Maybe Text)
nodeGroup_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NodeGroup' {Maybe Text
status :: Maybe Text
$sel:status:NodeGroup' :: NodeGroup -> Maybe Text
status} -> Maybe Text
status) (\s :: NodeGroup
s@NodeGroup' {} Maybe Text
a -> NodeGroup
s {$sel:status:NodeGroup' :: Maybe Text
status = Maybe Text
a} :: NodeGroup)

instance Data.FromXML NodeGroup where
  parseXML :: [Node] -> Either String NodeGroup
parseXML [Node]
x =
    Maybe Text
-> Maybe [NodeGroupMember]
-> Maybe Endpoint
-> Maybe Endpoint
-> Maybe Text
-> Maybe Text
-> NodeGroup
NodeGroup'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NodeGroupId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NodeGroupMembers"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"NodeGroupMember")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PrimaryEndpoint")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReaderEndpoint")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Slots")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Status")

instance Prelude.Hashable NodeGroup where
  hashWithSalt :: Int -> NodeGroup -> Int
hashWithSalt Int
_salt NodeGroup' {Maybe [NodeGroupMember]
Maybe Text
Maybe Endpoint
status :: Maybe Text
slots :: Maybe Text
readerEndpoint :: Maybe Endpoint
primaryEndpoint :: Maybe Endpoint
nodeGroupMembers :: Maybe [NodeGroupMember]
nodeGroupId :: Maybe Text
$sel:status:NodeGroup' :: NodeGroup -> Maybe Text
$sel:slots:NodeGroup' :: NodeGroup -> Maybe Text
$sel:readerEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
$sel:primaryEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
$sel:nodeGroupMembers:NodeGroup' :: NodeGroup -> Maybe [NodeGroupMember]
$sel:nodeGroupId:NodeGroup' :: NodeGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nodeGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NodeGroupMember]
nodeGroupMembers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Endpoint
primaryEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Endpoint
readerEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
slots
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
status

instance Prelude.NFData NodeGroup where
  rnf :: NodeGroup -> ()
rnf NodeGroup' {Maybe [NodeGroupMember]
Maybe Text
Maybe Endpoint
status :: Maybe Text
slots :: Maybe Text
readerEndpoint :: Maybe Endpoint
primaryEndpoint :: Maybe Endpoint
nodeGroupMembers :: Maybe [NodeGroupMember]
nodeGroupId :: Maybe Text
$sel:status:NodeGroup' :: NodeGroup -> Maybe Text
$sel:slots:NodeGroup' :: NodeGroup -> Maybe Text
$sel:readerEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
$sel:primaryEndpoint:NodeGroup' :: NodeGroup -> Maybe Endpoint
$sel:nodeGroupMembers:NodeGroup' :: NodeGroup -> Maybe [NodeGroupMember]
$sel:nodeGroupId:NodeGroup' :: NodeGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nodeGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NodeGroupMember]
nodeGroupMembers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Endpoint
primaryEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Endpoint
readerEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
slots
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status