{-# 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.Snapshot
-- 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.Snapshot 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.AutomaticFailoverStatus
import Amazonka.ElastiCache.Types.DataTieringStatus
import Amazonka.ElastiCache.Types.NodeSnapshot
import qualified Amazonka.Prelude as Prelude

-- | Represents a copy of an entire Redis cluster as of the time when the
-- snapshot was taken.
--
-- /See:/ 'newSnapshot' smart constructor.
data Snapshot = Snapshot'
  { -- | The ARN (Amazon Resource Name) of the snapshot.
    Snapshot -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | If you are running Redis engine version 6.0 or later, set this
    -- parameter to yes if you want to opt-in to the next auto minor version
    -- upgrade campaign. This parameter is disabled for previous versions.
    Snapshot -> Maybe Bool
autoMinorVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | Indicates the status of automatic failover for the source Redis
    -- replication group.
    Snapshot -> Maybe AutomaticFailoverStatus
automaticFailover :: Prelude.Maybe AutomaticFailoverStatus,
    -- | The date and time when the source cluster was created.
    Snapshot -> Maybe ISO8601
cacheClusterCreateTime :: Prelude.Maybe Data.ISO8601,
    -- | The user-supplied identifier of the source cluster.
    Snapshot -> Maybe Text
cacheClusterId :: Prelude.Maybe Prelude.Text,
    -- | The name of the compute and memory capacity node type for the source
    -- cluster.
    --
    -- The following node types are supported by ElastiCache. Generally
    -- speaking, the current generation types provide more memory and
    -- computational power at lower cost when compared to their equivalent
    -- previous generation counterparts.
    --
    -- -   General purpose:
    --
    --     -   Current generation:
    --
    --         __M6g node types__ (available only for Redis engine version
    --         5.0.6 onward and for Memcached engine version 1.5.16 onward):
    --         @cache.m6g.large@, @cache.m6g.xlarge@, @cache.m6g.2xlarge@,
    --         @cache.m6g.4xlarge@, @cache.m6g.8xlarge@, @cache.m6g.12xlarge@,
    --         @cache.m6g.16xlarge@
    --
    --         For region availability, see
    --         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
    --
    --         __M5 node types:__ @cache.m5.large@, @cache.m5.xlarge@,
    --         @cache.m5.2xlarge@, @cache.m5.4xlarge@, @cache.m5.12xlarge@,
    --         @cache.m5.24xlarge@
    --
    --         __M4 node types:__ @cache.m4.large@, @cache.m4.xlarge@,
    --         @cache.m4.2xlarge@, @cache.m4.4xlarge@, @cache.m4.10xlarge@
    --
    --         __T4g node types__ (available only for Redis engine version
    --         5.0.6 onward and Memcached engine version 1.5.16 onward):
    --         @cache.t4g.micro@, @cache.t4g.small@, @cache.t4g.medium@
    --
    --         __T3 node types:__ @cache.t3.micro@, @cache.t3.small@,
    --         @cache.t3.medium@
    --
    --         __T2 node types:__ @cache.t2.micro@, @cache.t2.small@,
    --         @cache.t2.medium@
    --
    --     -   Previous generation: (not recommended. Existing clusters are
    --         still supported but creation of new clusters is not supported
    --         for these types.)
    --
    --         __T1 node types:__ @cache.t1.micro@
    --
    --         __M1 node types:__ @cache.m1.small@, @cache.m1.medium@,
    --         @cache.m1.large@, @cache.m1.xlarge@
    --
    --         __M3 node types:__ @cache.m3.medium@, @cache.m3.large@,
    --         @cache.m3.xlarge@, @cache.m3.2xlarge@
    --
    -- -   Compute optimized:
    --
    --     -   Previous generation: (not recommended. Existing clusters are
    --         still supported but creation of new clusters is not supported
    --         for these types.)
    --
    --         __C1 node types:__ @cache.c1.xlarge@
    --
    -- -   Memory optimized:
    --
    --     -   Current generation:
    --
    --         __R6g node types__ (available only for Redis engine version
    --         5.0.6 onward and for Memcached engine version 1.5.16 onward).
    --
    --         @cache.r6g.large@, @cache.r6g.xlarge@, @cache.r6g.2xlarge@,
    --         @cache.r6g.4xlarge@, @cache.r6g.8xlarge@, @cache.r6g.12xlarge@,
    --         @cache.r6g.16xlarge@
    --
    --         For region availability, see
    --         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
    --
    --         __R5 node types:__ @cache.r5.large@, @cache.r5.xlarge@,
    --         @cache.r5.2xlarge@, @cache.r5.4xlarge@, @cache.r5.12xlarge@,
    --         @cache.r5.24xlarge@
    --
    --         __R4 node types:__ @cache.r4.large@, @cache.r4.xlarge@,
    --         @cache.r4.2xlarge@, @cache.r4.4xlarge@, @cache.r4.8xlarge@,
    --         @cache.r4.16xlarge@
    --
    --     -   Previous generation: (not recommended. Existing clusters are
    --         still supported but creation of new clusters is not supported
    --         for these types.)
    --
    --         __M2 node types:__ @cache.m2.xlarge@, @cache.m2.2xlarge@,
    --         @cache.m2.4xlarge@
    --
    --         __R3 node types:__ @cache.r3.large@, @cache.r3.xlarge@,
    --         @cache.r3.2xlarge@, @cache.r3.4xlarge@, @cache.r3.8xlarge@
    --
    -- __Additional node type info__
    --
    -- -   All current generation instance types are created in Amazon VPC by
    --     default.
    --
    -- -   Redis append-only files (AOF) are not supported for T1 or T2
    --     instances.
    --
    -- -   Redis Multi-AZ with automatic failover is not supported on T1
    --     instances.
    --
    -- -   Redis configuration variables @appendonly@ and @appendfsync@ are not
    --     supported on Redis version 2.8.22 and later.
    Snapshot -> Maybe Text
cacheNodeType :: Prelude.Maybe Prelude.Text,
    -- | The cache parameter group that is associated with the source cluster.
    Snapshot -> Maybe Text
cacheParameterGroupName :: Prelude.Maybe Prelude.Text,
    -- | The name of the cache subnet group associated with the source cluster.
    Snapshot -> Maybe Text
cacheSubnetGroupName :: Prelude.Maybe Prelude.Text,
    -- | Enables data tiering. Data tiering is only supported for replication
    -- groups using the r6gd node type. This parameter must be set to true when
    -- using r6gd nodes. For more information, see
    -- <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/data-tiering.html Data tiering>.
    Snapshot -> Maybe DataTieringStatus
dataTiering :: Prelude.Maybe DataTieringStatus,
    -- | The name of the cache engine (@memcached@ or @redis@) used by the source
    -- cluster.
    Snapshot -> Maybe Text
engine :: Prelude.Maybe Prelude.Text,
    -- | The version of the cache engine version that is used by the source
    -- cluster.
    Snapshot -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The ID of the KMS key used to encrypt the snapshot.
    Snapshot -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | A list of the cache nodes in the source cluster.
    Snapshot -> Maybe [NodeSnapshot]
nodeSnapshots :: Prelude.Maybe [NodeSnapshot],
    -- | The number of cache nodes in the source cluster.
    --
    -- For clusters running Redis, this value must be 1. For clusters running
    -- Memcached, this value must be between 1 and 40.
    Snapshot -> Maybe Int
numCacheNodes :: Prelude.Maybe Prelude.Int,
    -- | The number of node groups (shards) in this snapshot. When restoring from
    -- a snapshot, the number of node groups (shards) in the snapshot and in
    -- the restored replication group must be the same.
    Snapshot -> Maybe Int
numNodeGroups :: Prelude.Maybe Prelude.Int,
    -- | The port number used by each cache nodes in the source cluster.
    Snapshot -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    -- | The name of the Availability Zone in which the source cluster is
    -- located.
    Snapshot -> Maybe Text
preferredAvailabilityZone :: Prelude.Maybe Prelude.Text,
    -- | Specifies the weekly time range during which maintenance on the cluster
    -- is performed. It is specified as a range in the format
    -- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
    -- is a 60 minute period.
    --
    -- Valid values for @ddd@ are:
    --
    -- -   @sun@
    --
    -- -   @mon@
    --
    -- -   @tue@
    --
    -- -   @wed@
    --
    -- -   @thu@
    --
    -- -   @fri@
    --
    -- -   @sat@
    --
    -- Example: @sun:23:00-mon:01:30@
    Snapshot -> Maybe Text
preferredMaintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | The ARN (Amazon Resource Name) of the preferred outpost.
    Snapshot -> Maybe Text
preferredOutpostArn :: Prelude.Maybe Prelude.Text,
    -- | A description of the source replication group.
    Snapshot -> Maybe Text
replicationGroupDescription :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the source replication group.
    Snapshot -> Maybe Text
replicationGroupId :: Prelude.Maybe Prelude.Text,
    -- | The name of a snapshot. For an automatic snapshot, the name is
    -- system-generated. For a manual snapshot, this is the user-provided name.
    Snapshot -> Maybe Text
snapshotName :: Prelude.Maybe Prelude.Text,
    -- | For an automatic snapshot, the number of days for which ElastiCache
    -- retains the snapshot before deleting it.
    --
    -- For manual snapshots, this field reflects the @SnapshotRetentionLimit@
    -- for the source cluster when the snapshot was created. This field is
    -- otherwise ignored: Manual snapshots do not expire, and can only be
    -- deleted using the @DeleteSnapshot@ operation.
    --
    -- __Important__ If the value of SnapshotRetentionLimit is set to zero (0),
    -- backups are turned off.
    Snapshot -> Maybe Int
snapshotRetentionLimit :: Prelude.Maybe Prelude.Int,
    -- | Indicates whether the snapshot is from an automatic backup (@automated@)
    -- or was created manually (@manual@).
    Snapshot -> Maybe Text
snapshotSource :: Prelude.Maybe Prelude.Text,
    -- | The status of the snapshot. Valid values: @creating@ | @available@ |
    -- @restoring@ | @copying@ | @deleting@.
    Snapshot -> Maybe Text
snapshotStatus :: Prelude.Maybe Prelude.Text,
    -- | The daily time range during which ElastiCache takes daily snapshots of
    -- the source cluster.
    Snapshot -> Maybe Text
snapshotWindow :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) for the topic used by the source cluster
    -- for publishing notifications.
    Snapshot -> Maybe Text
topicArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Virtual Private Cloud identifier (VPC ID) of the cache subnet
    -- group for the source cluster.
    Snapshot -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (Snapshot -> Snapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Snapshot -> Snapshot -> Bool
$c/= :: Snapshot -> Snapshot -> Bool
== :: Snapshot -> Snapshot -> Bool
$c== :: Snapshot -> Snapshot -> Bool
Prelude.Eq, ReadPrec [Snapshot]
ReadPrec Snapshot
Int -> ReadS Snapshot
ReadS [Snapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Snapshot]
$creadListPrec :: ReadPrec [Snapshot]
readPrec :: ReadPrec Snapshot
$creadPrec :: ReadPrec Snapshot
readList :: ReadS [Snapshot]
$creadList :: ReadS [Snapshot]
readsPrec :: Int -> ReadS Snapshot
$creadsPrec :: Int -> ReadS Snapshot
Prelude.Read, Int -> Snapshot -> ShowS
[Snapshot] -> ShowS
Snapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Snapshot] -> ShowS
$cshowList :: [Snapshot] -> ShowS
show :: Snapshot -> String
$cshow :: Snapshot -> String
showsPrec :: Int -> Snapshot -> ShowS
$cshowsPrec :: Int -> Snapshot -> ShowS
Prelude.Show, forall x. Rep Snapshot x -> Snapshot
forall x. Snapshot -> Rep Snapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Snapshot x -> Snapshot
$cfrom :: forall x. Snapshot -> Rep Snapshot x
Prelude.Generic)

-- |
-- Create a value of 'Snapshot' 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:
--
-- 'arn', 'snapshot_arn' - The ARN (Amazon Resource Name) of the snapshot.
--
-- 'autoMinorVersionUpgrade', 'snapshot_autoMinorVersionUpgrade' - If you are running Redis engine version 6.0 or later, set this
-- parameter to yes if you want to opt-in to the next auto minor version
-- upgrade campaign. This parameter is disabled for previous versions.
--
-- 'automaticFailover', 'snapshot_automaticFailover' - Indicates the status of automatic failover for the source Redis
-- replication group.
--
-- 'cacheClusterCreateTime', 'snapshot_cacheClusterCreateTime' - The date and time when the source cluster was created.
--
-- 'cacheClusterId', 'snapshot_cacheClusterId' - The user-supplied identifier of the source cluster.
--
-- 'cacheNodeType', 'snapshot_cacheNodeType' - The name of the compute and memory capacity node type for the source
-- cluster.
--
-- The following node types are supported by ElastiCache. Generally
-- speaking, the current generation types provide more memory and
-- computational power at lower cost when compared to their equivalent
-- previous generation counterparts.
--
-- -   General purpose:
--
--     -   Current generation:
--
--         __M6g node types__ (available only for Redis engine version
--         5.0.6 onward and for Memcached engine version 1.5.16 onward):
--         @cache.m6g.large@, @cache.m6g.xlarge@, @cache.m6g.2xlarge@,
--         @cache.m6g.4xlarge@, @cache.m6g.8xlarge@, @cache.m6g.12xlarge@,
--         @cache.m6g.16xlarge@
--
--         For region availability, see
--         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
--
--         __M5 node types:__ @cache.m5.large@, @cache.m5.xlarge@,
--         @cache.m5.2xlarge@, @cache.m5.4xlarge@, @cache.m5.12xlarge@,
--         @cache.m5.24xlarge@
--
--         __M4 node types:__ @cache.m4.large@, @cache.m4.xlarge@,
--         @cache.m4.2xlarge@, @cache.m4.4xlarge@, @cache.m4.10xlarge@
--
--         __T4g node types__ (available only for Redis engine version
--         5.0.6 onward and Memcached engine version 1.5.16 onward):
--         @cache.t4g.micro@, @cache.t4g.small@, @cache.t4g.medium@
--
--         __T3 node types:__ @cache.t3.micro@, @cache.t3.small@,
--         @cache.t3.medium@
--
--         __T2 node types:__ @cache.t2.micro@, @cache.t2.small@,
--         @cache.t2.medium@
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __T1 node types:__ @cache.t1.micro@
--
--         __M1 node types:__ @cache.m1.small@, @cache.m1.medium@,
--         @cache.m1.large@, @cache.m1.xlarge@
--
--         __M3 node types:__ @cache.m3.medium@, @cache.m3.large@,
--         @cache.m3.xlarge@, @cache.m3.2xlarge@
--
-- -   Compute optimized:
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __C1 node types:__ @cache.c1.xlarge@
--
-- -   Memory optimized:
--
--     -   Current generation:
--
--         __R6g node types__ (available only for Redis engine version
--         5.0.6 onward and for Memcached engine version 1.5.16 onward).
--
--         @cache.r6g.large@, @cache.r6g.xlarge@, @cache.r6g.2xlarge@,
--         @cache.r6g.4xlarge@, @cache.r6g.8xlarge@, @cache.r6g.12xlarge@,
--         @cache.r6g.16xlarge@
--
--         For region availability, see
--         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
--
--         __R5 node types:__ @cache.r5.large@, @cache.r5.xlarge@,
--         @cache.r5.2xlarge@, @cache.r5.4xlarge@, @cache.r5.12xlarge@,
--         @cache.r5.24xlarge@
--
--         __R4 node types:__ @cache.r4.large@, @cache.r4.xlarge@,
--         @cache.r4.2xlarge@, @cache.r4.4xlarge@, @cache.r4.8xlarge@,
--         @cache.r4.16xlarge@
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __M2 node types:__ @cache.m2.xlarge@, @cache.m2.2xlarge@,
--         @cache.m2.4xlarge@
--
--         __R3 node types:__ @cache.r3.large@, @cache.r3.xlarge@,
--         @cache.r3.2xlarge@, @cache.r3.4xlarge@, @cache.r3.8xlarge@
--
-- __Additional node type info__
--
-- -   All current generation instance types are created in Amazon VPC by
--     default.
--
-- -   Redis append-only files (AOF) are not supported for T1 or T2
--     instances.
--
-- -   Redis Multi-AZ with automatic failover is not supported on T1
--     instances.
--
-- -   Redis configuration variables @appendonly@ and @appendfsync@ are not
--     supported on Redis version 2.8.22 and later.
--
-- 'cacheParameterGroupName', 'snapshot_cacheParameterGroupName' - The cache parameter group that is associated with the source cluster.
--
-- 'cacheSubnetGroupName', 'snapshot_cacheSubnetGroupName' - The name of the cache subnet group associated with the source cluster.
--
-- 'dataTiering', 'snapshot_dataTiering' - Enables data tiering. Data tiering is only supported for replication
-- groups using the r6gd node type. This parameter must be set to true when
-- using r6gd nodes. For more information, see
-- <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/data-tiering.html Data tiering>.
--
-- 'engine', 'snapshot_engine' - The name of the cache engine (@memcached@ or @redis@) used by the source
-- cluster.
--
-- 'engineVersion', 'snapshot_engineVersion' - The version of the cache engine version that is used by the source
-- cluster.
--
-- 'kmsKeyId', 'snapshot_kmsKeyId' - The ID of the KMS key used to encrypt the snapshot.
--
-- 'nodeSnapshots', 'snapshot_nodeSnapshots' - A list of the cache nodes in the source cluster.
--
-- 'numCacheNodes', 'snapshot_numCacheNodes' - The number of cache nodes in the source cluster.
--
-- For clusters running Redis, this value must be 1. For clusters running
-- Memcached, this value must be between 1 and 40.
--
-- 'numNodeGroups', 'snapshot_numNodeGroups' - The number of node groups (shards) in this snapshot. When restoring from
-- a snapshot, the number of node groups (shards) in the snapshot and in
-- the restored replication group must be the same.
--
-- 'port', 'snapshot_port' - The port number used by each cache nodes in the source cluster.
--
-- 'preferredAvailabilityZone', 'snapshot_preferredAvailabilityZone' - The name of the Availability Zone in which the source cluster is
-- located.
--
-- 'preferredMaintenanceWindow', 'snapshot_preferredMaintenanceWindow' - Specifies the weekly time range during which maintenance on the cluster
-- is performed. It is specified as a range in the format
-- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
-- is a 60 minute period.
--
-- Valid values for @ddd@ are:
--
-- -   @sun@
--
-- -   @mon@
--
-- -   @tue@
--
-- -   @wed@
--
-- -   @thu@
--
-- -   @fri@
--
-- -   @sat@
--
-- Example: @sun:23:00-mon:01:30@
--
-- 'preferredOutpostArn', 'snapshot_preferredOutpostArn' - The ARN (Amazon Resource Name) of the preferred outpost.
--
-- 'replicationGroupDescription', 'snapshot_replicationGroupDescription' - A description of the source replication group.
--
-- 'replicationGroupId', 'snapshot_replicationGroupId' - The unique identifier of the source replication group.
--
-- 'snapshotName', 'snapshot_snapshotName' - The name of a snapshot. For an automatic snapshot, the name is
-- system-generated. For a manual snapshot, this is the user-provided name.
--
-- 'snapshotRetentionLimit', 'snapshot_snapshotRetentionLimit' - For an automatic snapshot, the number of days for which ElastiCache
-- retains the snapshot before deleting it.
--
-- For manual snapshots, this field reflects the @SnapshotRetentionLimit@
-- for the source cluster when the snapshot was created. This field is
-- otherwise ignored: Manual snapshots do not expire, and can only be
-- deleted using the @DeleteSnapshot@ operation.
--
-- __Important__ If the value of SnapshotRetentionLimit is set to zero (0),
-- backups are turned off.
--
-- 'snapshotSource', 'snapshot_snapshotSource' - Indicates whether the snapshot is from an automatic backup (@automated@)
-- or was created manually (@manual@).
--
-- 'snapshotStatus', 'snapshot_snapshotStatus' - The status of the snapshot. Valid values: @creating@ | @available@ |
-- @restoring@ | @copying@ | @deleting@.
--
-- 'snapshotWindow', 'snapshot_snapshotWindow' - The daily time range during which ElastiCache takes daily snapshots of
-- the source cluster.
--
-- 'topicArn', 'snapshot_topicArn' - The Amazon Resource Name (ARN) for the topic used by the source cluster
-- for publishing notifications.
--
-- 'vpcId', 'snapshot_vpcId' - The Amazon Virtual Private Cloud identifier (VPC ID) of the cache subnet
-- group for the source cluster.
newSnapshot ::
  Snapshot
newSnapshot :: Snapshot
newSnapshot =
  Snapshot'
    { $sel:arn:Snapshot' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:autoMinorVersionUpgrade:Snapshot' :: Maybe Bool
autoMinorVersionUpgrade = forall a. Maybe a
Prelude.Nothing,
      $sel:automaticFailover:Snapshot' :: Maybe AutomaticFailoverStatus
automaticFailover = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheClusterCreateTime:Snapshot' :: Maybe ISO8601
cacheClusterCreateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheClusterId:Snapshot' :: Maybe Text
cacheClusterId = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheNodeType:Snapshot' :: Maybe Text
cacheNodeType = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheParameterGroupName:Snapshot' :: Maybe Text
cacheParameterGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheSubnetGroupName:Snapshot' :: Maybe Text
cacheSubnetGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:dataTiering:Snapshot' :: Maybe DataTieringStatus
dataTiering = forall a. Maybe a
Prelude.Nothing,
      $sel:engine:Snapshot' :: Maybe Text
engine = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:Snapshot' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:Snapshot' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:nodeSnapshots:Snapshot' :: Maybe [NodeSnapshot]
nodeSnapshots = forall a. Maybe a
Prelude.Nothing,
      $sel:numCacheNodes:Snapshot' :: Maybe Int
numCacheNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:numNodeGroups:Snapshot' :: Maybe Int
numNodeGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:port:Snapshot' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredAvailabilityZone:Snapshot' :: Maybe Text
preferredAvailabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredMaintenanceWindow:Snapshot' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredOutpostArn:Snapshot' :: Maybe Text
preferredOutpostArn = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationGroupDescription:Snapshot' :: Maybe Text
replicationGroupDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationGroupId:Snapshot' :: Maybe Text
replicationGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotName:Snapshot' :: Maybe Text
snapshotName = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotRetentionLimit:Snapshot' :: Maybe Int
snapshotRetentionLimit = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotSource:Snapshot' :: Maybe Text
snapshotSource = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotStatus:Snapshot' :: Maybe Text
snapshotStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotWindow:Snapshot' :: Maybe Text
snapshotWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:topicArn:Snapshot' :: Maybe Text
topicArn = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:Snapshot' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

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

-- | If you are running Redis engine version 6.0 or later, set this
-- parameter to yes if you want to opt-in to the next auto minor version
-- upgrade campaign. This parameter is disabled for previous versions.
snapshot_autoMinorVersionUpgrade :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Bool)
snapshot_autoMinorVersionUpgrade :: Lens' Snapshot (Maybe Bool)
snapshot_autoMinorVersionUpgrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Bool
autoMinorVersionUpgrade :: Maybe Bool
$sel:autoMinorVersionUpgrade:Snapshot' :: Snapshot -> Maybe Bool
autoMinorVersionUpgrade} -> Maybe Bool
autoMinorVersionUpgrade) (\s :: Snapshot
s@Snapshot' {} Maybe Bool
a -> Snapshot
s {$sel:autoMinorVersionUpgrade:Snapshot' :: Maybe Bool
autoMinorVersionUpgrade = Maybe Bool
a} :: Snapshot)

-- | Indicates the status of automatic failover for the source Redis
-- replication group.
snapshot_automaticFailover :: Lens.Lens' Snapshot (Prelude.Maybe AutomaticFailoverStatus)
snapshot_automaticFailover :: Lens' Snapshot (Maybe AutomaticFailoverStatus)
snapshot_automaticFailover = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe AutomaticFailoverStatus
automaticFailover :: Maybe AutomaticFailoverStatus
$sel:automaticFailover:Snapshot' :: Snapshot -> Maybe AutomaticFailoverStatus
automaticFailover} -> Maybe AutomaticFailoverStatus
automaticFailover) (\s :: Snapshot
s@Snapshot' {} Maybe AutomaticFailoverStatus
a -> Snapshot
s {$sel:automaticFailover:Snapshot' :: Maybe AutomaticFailoverStatus
automaticFailover = Maybe AutomaticFailoverStatus
a} :: Snapshot)

-- | The date and time when the source cluster was created.
snapshot_cacheClusterCreateTime :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.UTCTime)
snapshot_cacheClusterCreateTime :: Lens' Snapshot (Maybe UTCTime)
snapshot_cacheClusterCreateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe ISO8601
cacheClusterCreateTime :: Maybe ISO8601
$sel:cacheClusterCreateTime:Snapshot' :: Snapshot -> Maybe ISO8601
cacheClusterCreateTime} -> Maybe ISO8601
cacheClusterCreateTime) (\s :: Snapshot
s@Snapshot' {} Maybe ISO8601
a -> Snapshot
s {$sel:cacheClusterCreateTime:Snapshot' :: Maybe ISO8601
cacheClusterCreateTime = Maybe ISO8601
a} :: Snapshot) 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 user-supplied identifier of the source cluster.
snapshot_cacheClusterId :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_cacheClusterId :: Lens' Snapshot (Maybe Text)
snapshot_cacheClusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
cacheClusterId :: Maybe Text
$sel:cacheClusterId:Snapshot' :: Snapshot -> Maybe Text
cacheClusterId} -> Maybe Text
cacheClusterId) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:cacheClusterId:Snapshot' :: Maybe Text
cacheClusterId = Maybe Text
a} :: Snapshot)

-- | The name of the compute and memory capacity node type for the source
-- cluster.
--
-- The following node types are supported by ElastiCache. Generally
-- speaking, the current generation types provide more memory and
-- computational power at lower cost when compared to their equivalent
-- previous generation counterparts.
--
-- -   General purpose:
--
--     -   Current generation:
--
--         __M6g node types__ (available only for Redis engine version
--         5.0.6 onward and for Memcached engine version 1.5.16 onward):
--         @cache.m6g.large@, @cache.m6g.xlarge@, @cache.m6g.2xlarge@,
--         @cache.m6g.4xlarge@, @cache.m6g.8xlarge@, @cache.m6g.12xlarge@,
--         @cache.m6g.16xlarge@
--
--         For region availability, see
--         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
--
--         __M5 node types:__ @cache.m5.large@, @cache.m5.xlarge@,
--         @cache.m5.2xlarge@, @cache.m5.4xlarge@, @cache.m5.12xlarge@,
--         @cache.m5.24xlarge@
--
--         __M4 node types:__ @cache.m4.large@, @cache.m4.xlarge@,
--         @cache.m4.2xlarge@, @cache.m4.4xlarge@, @cache.m4.10xlarge@
--
--         __T4g node types__ (available only for Redis engine version
--         5.0.6 onward and Memcached engine version 1.5.16 onward):
--         @cache.t4g.micro@, @cache.t4g.small@, @cache.t4g.medium@
--
--         __T3 node types:__ @cache.t3.micro@, @cache.t3.small@,
--         @cache.t3.medium@
--
--         __T2 node types:__ @cache.t2.micro@, @cache.t2.small@,
--         @cache.t2.medium@
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __T1 node types:__ @cache.t1.micro@
--
--         __M1 node types:__ @cache.m1.small@, @cache.m1.medium@,
--         @cache.m1.large@, @cache.m1.xlarge@
--
--         __M3 node types:__ @cache.m3.medium@, @cache.m3.large@,
--         @cache.m3.xlarge@, @cache.m3.2xlarge@
--
-- -   Compute optimized:
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __C1 node types:__ @cache.c1.xlarge@
--
-- -   Memory optimized:
--
--     -   Current generation:
--
--         __R6g node types__ (available only for Redis engine version
--         5.0.6 onward and for Memcached engine version 1.5.16 onward).
--
--         @cache.r6g.large@, @cache.r6g.xlarge@, @cache.r6g.2xlarge@,
--         @cache.r6g.4xlarge@, @cache.r6g.8xlarge@, @cache.r6g.12xlarge@,
--         @cache.r6g.16xlarge@
--
--         For region availability, see
--         <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/CacheNodes.SupportedTypes.html#CacheNodes.SupportedTypesByRegion Supported Node Types>
--
--         __R5 node types:__ @cache.r5.large@, @cache.r5.xlarge@,
--         @cache.r5.2xlarge@, @cache.r5.4xlarge@, @cache.r5.12xlarge@,
--         @cache.r5.24xlarge@
--
--         __R4 node types:__ @cache.r4.large@, @cache.r4.xlarge@,
--         @cache.r4.2xlarge@, @cache.r4.4xlarge@, @cache.r4.8xlarge@,
--         @cache.r4.16xlarge@
--
--     -   Previous generation: (not recommended. Existing clusters are
--         still supported but creation of new clusters is not supported
--         for these types.)
--
--         __M2 node types:__ @cache.m2.xlarge@, @cache.m2.2xlarge@,
--         @cache.m2.4xlarge@
--
--         __R3 node types:__ @cache.r3.large@, @cache.r3.xlarge@,
--         @cache.r3.2xlarge@, @cache.r3.4xlarge@, @cache.r3.8xlarge@
--
-- __Additional node type info__
--
-- -   All current generation instance types are created in Amazon VPC by
--     default.
--
-- -   Redis append-only files (AOF) are not supported for T1 or T2
--     instances.
--
-- -   Redis Multi-AZ with automatic failover is not supported on T1
--     instances.
--
-- -   Redis configuration variables @appendonly@ and @appendfsync@ are not
--     supported on Redis version 2.8.22 and later.
snapshot_cacheNodeType :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_cacheNodeType :: Lens' Snapshot (Maybe Text)
snapshot_cacheNodeType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
cacheNodeType :: Maybe Text
$sel:cacheNodeType:Snapshot' :: Snapshot -> Maybe Text
cacheNodeType} -> Maybe Text
cacheNodeType) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:cacheNodeType:Snapshot' :: Maybe Text
cacheNodeType = Maybe Text
a} :: Snapshot)

-- | The cache parameter group that is associated with the source cluster.
snapshot_cacheParameterGroupName :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_cacheParameterGroupName :: Lens' Snapshot (Maybe Text)
snapshot_cacheParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
cacheParameterGroupName :: Maybe Text
$sel:cacheParameterGroupName:Snapshot' :: Snapshot -> Maybe Text
cacheParameterGroupName} -> Maybe Text
cacheParameterGroupName) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:cacheParameterGroupName:Snapshot' :: Maybe Text
cacheParameterGroupName = Maybe Text
a} :: Snapshot)

-- | The name of the cache subnet group associated with the source cluster.
snapshot_cacheSubnetGroupName :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_cacheSubnetGroupName :: Lens' Snapshot (Maybe Text)
snapshot_cacheSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
cacheSubnetGroupName :: Maybe Text
$sel:cacheSubnetGroupName:Snapshot' :: Snapshot -> Maybe Text
cacheSubnetGroupName} -> Maybe Text
cacheSubnetGroupName) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:cacheSubnetGroupName:Snapshot' :: Maybe Text
cacheSubnetGroupName = Maybe Text
a} :: Snapshot)

-- | Enables data tiering. Data tiering is only supported for replication
-- groups using the r6gd node type. This parameter must be set to true when
-- using r6gd nodes. For more information, see
-- <https://docs.aws.amazon.com/AmazonElastiCache/latest/red-ug/data-tiering.html Data tiering>.
snapshot_dataTiering :: Lens.Lens' Snapshot (Prelude.Maybe DataTieringStatus)
snapshot_dataTiering :: Lens' Snapshot (Maybe DataTieringStatus)
snapshot_dataTiering = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe DataTieringStatus
dataTiering :: Maybe DataTieringStatus
$sel:dataTiering:Snapshot' :: Snapshot -> Maybe DataTieringStatus
dataTiering} -> Maybe DataTieringStatus
dataTiering) (\s :: Snapshot
s@Snapshot' {} Maybe DataTieringStatus
a -> Snapshot
s {$sel:dataTiering:Snapshot' :: Maybe DataTieringStatus
dataTiering = Maybe DataTieringStatus
a} :: Snapshot)

-- | The name of the cache engine (@memcached@ or @redis@) used by the source
-- cluster.
snapshot_engine :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_engine :: Lens' Snapshot (Maybe Text)
snapshot_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
engine :: Maybe Text
$sel:engine:Snapshot' :: Snapshot -> Maybe Text
engine} -> Maybe Text
engine) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:engine:Snapshot' :: Maybe Text
engine = Maybe Text
a} :: Snapshot)

-- | The version of the cache engine version that is used by the source
-- cluster.
snapshot_engineVersion :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_engineVersion :: Lens' Snapshot (Maybe Text)
snapshot_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:Snapshot' :: Snapshot -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:engineVersion:Snapshot' :: Maybe Text
engineVersion = Maybe Text
a} :: Snapshot)

-- | The ID of the KMS key used to encrypt the snapshot.
snapshot_kmsKeyId :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_kmsKeyId :: Lens' Snapshot (Maybe Text)
snapshot_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:Snapshot' :: Snapshot -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:kmsKeyId:Snapshot' :: Maybe Text
kmsKeyId = Maybe Text
a} :: Snapshot)

-- | A list of the cache nodes in the source cluster.
snapshot_nodeSnapshots :: Lens.Lens' Snapshot (Prelude.Maybe [NodeSnapshot])
snapshot_nodeSnapshots :: Lens' Snapshot (Maybe [NodeSnapshot])
snapshot_nodeSnapshots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe [NodeSnapshot]
nodeSnapshots :: Maybe [NodeSnapshot]
$sel:nodeSnapshots:Snapshot' :: Snapshot -> Maybe [NodeSnapshot]
nodeSnapshots} -> Maybe [NodeSnapshot]
nodeSnapshots) (\s :: Snapshot
s@Snapshot' {} Maybe [NodeSnapshot]
a -> Snapshot
s {$sel:nodeSnapshots:Snapshot' :: Maybe [NodeSnapshot]
nodeSnapshots = Maybe [NodeSnapshot]
a} :: Snapshot) 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 number of cache nodes in the source cluster.
--
-- For clusters running Redis, this value must be 1. For clusters running
-- Memcached, this value must be between 1 and 40.
snapshot_numCacheNodes :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Int)
snapshot_numCacheNodes :: Lens' Snapshot (Maybe Int)
snapshot_numCacheNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Int
numCacheNodes :: Maybe Int
$sel:numCacheNodes:Snapshot' :: Snapshot -> Maybe Int
numCacheNodes} -> Maybe Int
numCacheNodes) (\s :: Snapshot
s@Snapshot' {} Maybe Int
a -> Snapshot
s {$sel:numCacheNodes:Snapshot' :: Maybe Int
numCacheNodes = Maybe Int
a} :: Snapshot)

-- | The number of node groups (shards) in this snapshot. When restoring from
-- a snapshot, the number of node groups (shards) in the snapshot and in
-- the restored replication group must be the same.
snapshot_numNodeGroups :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Int)
snapshot_numNodeGroups :: Lens' Snapshot (Maybe Int)
snapshot_numNodeGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Int
numNodeGroups :: Maybe Int
$sel:numNodeGroups:Snapshot' :: Snapshot -> Maybe Int
numNodeGroups} -> Maybe Int
numNodeGroups) (\s :: Snapshot
s@Snapshot' {} Maybe Int
a -> Snapshot
s {$sel:numNodeGroups:Snapshot' :: Maybe Int
numNodeGroups = Maybe Int
a} :: Snapshot)

-- | The port number used by each cache nodes in the source cluster.
snapshot_port :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Int)
snapshot_port :: Lens' Snapshot (Maybe Int)
snapshot_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Int
port :: Maybe Int
$sel:port:Snapshot' :: Snapshot -> Maybe Int
port} -> Maybe Int
port) (\s :: Snapshot
s@Snapshot' {} Maybe Int
a -> Snapshot
s {$sel:port:Snapshot' :: Maybe Int
port = Maybe Int
a} :: Snapshot)

-- | The name of the Availability Zone in which the source cluster is
-- located.
snapshot_preferredAvailabilityZone :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_preferredAvailabilityZone :: Lens' Snapshot (Maybe Text)
snapshot_preferredAvailabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
preferredAvailabilityZone :: Maybe Text
$sel:preferredAvailabilityZone:Snapshot' :: Snapshot -> Maybe Text
preferredAvailabilityZone} -> Maybe Text
preferredAvailabilityZone) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:preferredAvailabilityZone:Snapshot' :: Maybe Text
preferredAvailabilityZone = Maybe Text
a} :: Snapshot)

-- | Specifies the weekly time range during which maintenance on the cluster
-- is performed. It is specified as a range in the format
-- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
-- is a 60 minute period.
--
-- Valid values for @ddd@ are:
--
-- -   @sun@
--
-- -   @mon@
--
-- -   @tue@
--
-- -   @wed@
--
-- -   @thu@
--
-- -   @fri@
--
-- -   @sat@
--
-- Example: @sun:23:00-mon:01:30@
snapshot_preferredMaintenanceWindow :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_preferredMaintenanceWindow :: Lens' Snapshot (Maybe Text)
snapshot_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:Snapshot' :: Snapshot -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:preferredMaintenanceWindow:Snapshot' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: Snapshot)

-- | The ARN (Amazon Resource Name) of the preferred outpost.
snapshot_preferredOutpostArn :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_preferredOutpostArn :: Lens' Snapshot (Maybe Text)
snapshot_preferredOutpostArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
preferredOutpostArn :: Maybe Text
$sel:preferredOutpostArn:Snapshot' :: Snapshot -> Maybe Text
preferredOutpostArn} -> Maybe Text
preferredOutpostArn) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:preferredOutpostArn:Snapshot' :: Maybe Text
preferredOutpostArn = Maybe Text
a} :: Snapshot)

-- | A description of the source replication group.
snapshot_replicationGroupDescription :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_replicationGroupDescription :: Lens' Snapshot (Maybe Text)
snapshot_replicationGroupDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
replicationGroupDescription :: Maybe Text
$sel:replicationGroupDescription:Snapshot' :: Snapshot -> Maybe Text
replicationGroupDescription} -> Maybe Text
replicationGroupDescription) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:replicationGroupDescription:Snapshot' :: Maybe Text
replicationGroupDescription = Maybe Text
a} :: Snapshot)

-- | The unique identifier of the source replication group.
snapshot_replicationGroupId :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_replicationGroupId :: Lens' Snapshot (Maybe Text)
snapshot_replicationGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
replicationGroupId :: Maybe Text
$sel:replicationGroupId:Snapshot' :: Snapshot -> Maybe Text
replicationGroupId} -> Maybe Text
replicationGroupId) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:replicationGroupId:Snapshot' :: Maybe Text
replicationGroupId = Maybe Text
a} :: Snapshot)

-- | The name of a snapshot. For an automatic snapshot, the name is
-- system-generated. For a manual snapshot, this is the user-provided name.
snapshot_snapshotName :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_snapshotName :: Lens' Snapshot (Maybe Text)
snapshot_snapshotName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
snapshotName :: Maybe Text
$sel:snapshotName:Snapshot' :: Snapshot -> Maybe Text
snapshotName} -> Maybe Text
snapshotName) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:snapshotName:Snapshot' :: Maybe Text
snapshotName = Maybe Text
a} :: Snapshot)

-- | For an automatic snapshot, the number of days for which ElastiCache
-- retains the snapshot before deleting it.
--
-- For manual snapshots, this field reflects the @SnapshotRetentionLimit@
-- for the source cluster when the snapshot was created. This field is
-- otherwise ignored: Manual snapshots do not expire, and can only be
-- deleted using the @DeleteSnapshot@ operation.
--
-- __Important__ If the value of SnapshotRetentionLimit is set to zero (0),
-- backups are turned off.
snapshot_snapshotRetentionLimit :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Int)
snapshot_snapshotRetentionLimit :: Lens' Snapshot (Maybe Int)
snapshot_snapshotRetentionLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Int
snapshotRetentionLimit :: Maybe Int
$sel:snapshotRetentionLimit:Snapshot' :: Snapshot -> Maybe Int
snapshotRetentionLimit} -> Maybe Int
snapshotRetentionLimit) (\s :: Snapshot
s@Snapshot' {} Maybe Int
a -> Snapshot
s {$sel:snapshotRetentionLimit:Snapshot' :: Maybe Int
snapshotRetentionLimit = Maybe Int
a} :: Snapshot)

-- | Indicates whether the snapshot is from an automatic backup (@automated@)
-- or was created manually (@manual@).
snapshot_snapshotSource :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_snapshotSource :: Lens' Snapshot (Maybe Text)
snapshot_snapshotSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
snapshotSource :: Maybe Text
$sel:snapshotSource:Snapshot' :: Snapshot -> Maybe Text
snapshotSource} -> Maybe Text
snapshotSource) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:snapshotSource:Snapshot' :: Maybe Text
snapshotSource = Maybe Text
a} :: Snapshot)

-- | The status of the snapshot. Valid values: @creating@ | @available@ |
-- @restoring@ | @copying@ | @deleting@.
snapshot_snapshotStatus :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_snapshotStatus :: Lens' Snapshot (Maybe Text)
snapshot_snapshotStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
snapshotStatus :: Maybe Text
$sel:snapshotStatus:Snapshot' :: Snapshot -> Maybe Text
snapshotStatus} -> Maybe Text
snapshotStatus) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:snapshotStatus:Snapshot' :: Maybe Text
snapshotStatus = Maybe Text
a} :: Snapshot)

-- | The daily time range during which ElastiCache takes daily snapshots of
-- the source cluster.
snapshot_snapshotWindow :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_snapshotWindow :: Lens' Snapshot (Maybe Text)
snapshot_snapshotWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
snapshotWindow :: Maybe Text
$sel:snapshotWindow:Snapshot' :: Snapshot -> Maybe Text
snapshotWindow} -> Maybe Text
snapshotWindow) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:snapshotWindow:Snapshot' :: Maybe Text
snapshotWindow = Maybe Text
a} :: Snapshot)

-- | The Amazon Resource Name (ARN) for the topic used by the source cluster
-- for publishing notifications.
snapshot_topicArn :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_topicArn :: Lens' Snapshot (Maybe Text)
snapshot_topicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
topicArn :: Maybe Text
$sel:topicArn:Snapshot' :: Snapshot -> Maybe Text
topicArn} -> Maybe Text
topicArn) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:topicArn:Snapshot' :: Maybe Text
topicArn = Maybe Text
a} :: Snapshot)

-- | The Amazon Virtual Private Cloud identifier (VPC ID) of the cache subnet
-- group for the source cluster.
snapshot_vpcId :: Lens.Lens' Snapshot (Prelude.Maybe Prelude.Text)
snapshot_vpcId :: Lens' Snapshot (Maybe Text)
snapshot_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Snapshot' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:Snapshot' :: Snapshot -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: Snapshot
s@Snapshot' {} Maybe Text
a -> Snapshot
s {$sel:vpcId:Snapshot' :: Maybe Text
vpcId = Maybe Text
a} :: Snapshot)

instance Data.FromXML Snapshot where
  parseXML :: [Node] -> Either String Snapshot
parseXML [Node]
x =
    Maybe Text
-> Maybe Bool
-> Maybe AutomaticFailoverStatus
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DataTieringStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [NodeSnapshot]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Snapshot
Snapshot'
      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
"ARN")
      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
"AutoMinorVersionUpgrade")
      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
"AutomaticFailover")
      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
"CacheClusterCreateTime")
      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
"CacheClusterId")
      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
"CacheNodeType")
      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
"CacheParameterGroupName")
      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
"CacheSubnetGroupName")
      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
"DataTiering")
      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
"Engine")
      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
"EngineVersion")
      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
"KmsKeyId")
      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
"NodeSnapshots"
                      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
"NodeSnapshot")
                  )
      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
"NumCacheNodes")
      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
"NumNodeGroups")
      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
"Port")
      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
"PreferredAvailabilityZone")
      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
"PreferredMaintenanceWindow")
      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
"PreferredOutpostArn")
      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
"ReplicationGroupDescription")
      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
"ReplicationGroupId")
      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
"SnapshotName")
      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
"SnapshotRetentionLimit")
      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
"SnapshotSource")
      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
"SnapshotStatus")
      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
"SnapshotWindow")
      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
"TopicArn")
      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
"VpcId")

instance Prelude.Hashable Snapshot where
  hashWithSalt :: Int -> Snapshot -> Int
hashWithSalt Int
_salt Snapshot' {Maybe Bool
Maybe Int
Maybe [NodeSnapshot]
Maybe Text
Maybe ISO8601
Maybe AutomaticFailoverStatus
Maybe DataTieringStatus
vpcId :: Maybe Text
topicArn :: Maybe Text
snapshotWindow :: Maybe Text
snapshotStatus :: Maybe Text
snapshotSource :: Maybe Text
snapshotRetentionLimit :: Maybe Int
snapshotName :: Maybe Text
replicationGroupId :: Maybe Text
replicationGroupDescription :: Maybe Text
preferredOutpostArn :: Maybe Text
preferredMaintenanceWindow :: Maybe Text
preferredAvailabilityZone :: Maybe Text
port :: Maybe Int
numNodeGroups :: Maybe Int
numCacheNodes :: Maybe Int
nodeSnapshots :: Maybe [NodeSnapshot]
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
engine :: Maybe Text
dataTiering :: Maybe DataTieringStatus
cacheSubnetGroupName :: Maybe Text
cacheParameterGroupName :: Maybe Text
cacheNodeType :: Maybe Text
cacheClusterId :: Maybe Text
cacheClusterCreateTime :: Maybe ISO8601
automaticFailover :: Maybe AutomaticFailoverStatus
autoMinorVersionUpgrade :: Maybe Bool
arn :: Maybe Text
$sel:vpcId:Snapshot' :: Snapshot -> Maybe Text
$sel:topicArn:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotWindow:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotStatus:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotSource:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotRetentionLimit:Snapshot' :: Snapshot -> Maybe Int
$sel:snapshotName:Snapshot' :: Snapshot -> Maybe Text
$sel:replicationGroupId:Snapshot' :: Snapshot -> Maybe Text
$sel:replicationGroupDescription:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredOutpostArn:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredMaintenanceWindow:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredAvailabilityZone:Snapshot' :: Snapshot -> Maybe Text
$sel:port:Snapshot' :: Snapshot -> Maybe Int
$sel:numNodeGroups:Snapshot' :: Snapshot -> Maybe Int
$sel:numCacheNodes:Snapshot' :: Snapshot -> Maybe Int
$sel:nodeSnapshots:Snapshot' :: Snapshot -> Maybe [NodeSnapshot]
$sel:kmsKeyId:Snapshot' :: Snapshot -> Maybe Text
$sel:engineVersion:Snapshot' :: Snapshot -> Maybe Text
$sel:engine:Snapshot' :: Snapshot -> Maybe Text
$sel:dataTiering:Snapshot' :: Snapshot -> Maybe DataTieringStatus
$sel:cacheSubnetGroupName:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheParameterGroupName:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheNodeType:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheClusterId:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheClusterCreateTime:Snapshot' :: Snapshot -> Maybe ISO8601
$sel:automaticFailover:Snapshot' :: Snapshot -> Maybe AutomaticFailoverStatus
$sel:autoMinorVersionUpgrade:Snapshot' :: Snapshot -> Maybe Bool
$sel:arn:Snapshot' :: Snapshot -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoMinorVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutomaticFailoverStatus
automaticFailover
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
cacheClusterCreateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cacheClusterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cacheNodeType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cacheParameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cacheSubnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataTieringStatus
dataTiering
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engine
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NodeSnapshot]
nodeSnapshots
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numCacheNodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numNodeGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredAvailabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredMaintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredOutpostArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
replicationGroupDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
replicationGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
snapshotRetentionLimit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
topicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData Snapshot where
  rnf :: Snapshot -> ()
rnf Snapshot' {Maybe Bool
Maybe Int
Maybe [NodeSnapshot]
Maybe Text
Maybe ISO8601
Maybe AutomaticFailoverStatus
Maybe DataTieringStatus
vpcId :: Maybe Text
topicArn :: Maybe Text
snapshotWindow :: Maybe Text
snapshotStatus :: Maybe Text
snapshotSource :: Maybe Text
snapshotRetentionLimit :: Maybe Int
snapshotName :: Maybe Text
replicationGroupId :: Maybe Text
replicationGroupDescription :: Maybe Text
preferredOutpostArn :: Maybe Text
preferredMaintenanceWindow :: Maybe Text
preferredAvailabilityZone :: Maybe Text
port :: Maybe Int
numNodeGroups :: Maybe Int
numCacheNodes :: Maybe Int
nodeSnapshots :: Maybe [NodeSnapshot]
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
engine :: Maybe Text
dataTiering :: Maybe DataTieringStatus
cacheSubnetGroupName :: Maybe Text
cacheParameterGroupName :: Maybe Text
cacheNodeType :: Maybe Text
cacheClusterId :: Maybe Text
cacheClusterCreateTime :: Maybe ISO8601
automaticFailover :: Maybe AutomaticFailoverStatus
autoMinorVersionUpgrade :: Maybe Bool
arn :: Maybe Text
$sel:vpcId:Snapshot' :: Snapshot -> Maybe Text
$sel:topicArn:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotWindow:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotStatus:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotSource:Snapshot' :: Snapshot -> Maybe Text
$sel:snapshotRetentionLimit:Snapshot' :: Snapshot -> Maybe Int
$sel:snapshotName:Snapshot' :: Snapshot -> Maybe Text
$sel:replicationGroupId:Snapshot' :: Snapshot -> Maybe Text
$sel:replicationGroupDescription:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredOutpostArn:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredMaintenanceWindow:Snapshot' :: Snapshot -> Maybe Text
$sel:preferredAvailabilityZone:Snapshot' :: Snapshot -> Maybe Text
$sel:port:Snapshot' :: Snapshot -> Maybe Int
$sel:numNodeGroups:Snapshot' :: Snapshot -> Maybe Int
$sel:numCacheNodes:Snapshot' :: Snapshot -> Maybe Int
$sel:nodeSnapshots:Snapshot' :: Snapshot -> Maybe [NodeSnapshot]
$sel:kmsKeyId:Snapshot' :: Snapshot -> Maybe Text
$sel:engineVersion:Snapshot' :: Snapshot -> Maybe Text
$sel:engine:Snapshot' :: Snapshot -> Maybe Text
$sel:dataTiering:Snapshot' :: Snapshot -> Maybe DataTieringStatus
$sel:cacheSubnetGroupName:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheParameterGroupName:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheNodeType:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheClusterId:Snapshot' :: Snapshot -> Maybe Text
$sel:cacheClusterCreateTime:Snapshot' :: Snapshot -> Maybe ISO8601
$sel:automaticFailover:Snapshot' :: Snapshot -> Maybe AutomaticFailoverStatus
$sel:autoMinorVersionUpgrade:Snapshot' :: Snapshot -> Maybe Bool
$sel:arn:Snapshot' :: Snapshot -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoMinorVersionUpgrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomaticFailoverStatus
automaticFailover
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
cacheClusterCreateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cacheClusterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cacheNodeType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cacheParameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cacheSubnetGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataTieringStatus
dataTiering
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engine
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NodeSnapshot]
nodeSnapshots
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numCacheNodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numNodeGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
preferredAvailabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
preferredMaintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
preferredOutpostArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
replicationGroupDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
replicationGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
snapshotRetentionLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
snapshotSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
snapshotStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
snapshotWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
topicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
vpcId