{-# 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.CloudHSMV2.Types.Backup
-- 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.CloudHSMV2.Types.Backup where

import Amazonka.CloudHSMV2.Types.BackupState
import Amazonka.CloudHSMV2.Types.Tag
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Contains information about a backup of an AWS CloudHSM cluster. All
-- backup objects contain the @BackupId@, @BackupState@, @ClusterId@, and
-- @CreateTimestamp@ parameters. Backups that were copied into a
-- destination region additionally contain the @CopyTimestamp@,
-- @SourceBackup@, @SourceCluster@, and @SourceRegion@ parameters. A backup
-- that is pending deletion will include the @DeleteTimestamp@ parameter.
--
-- /See:/ 'newBackup' smart constructor.
data Backup = Backup'
  { -- | The state of the backup.
    Backup -> Maybe BackupState
backupState :: Prelude.Maybe BackupState,
    -- | The identifier (ID) of the cluster that was backed up.
    Backup -> Maybe Text
clusterId :: Prelude.Maybe Prelude.Text,
    -- | The date and time when the backup was copied from a source backup.
    Backup -> Maybe POSIX
copyTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The date and time when the backup was created.
    Backup -> Maybe POSIX
createTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The date and time when the backup will be permanently deleted.
    Backup -> Maybe POSIX
deleteTimestamp :: Prelude.Maybe Data.POSIX,
    -- | Specifies whether the service should exempt a backup from the retention
    -- policy for the cluster. @True@ exempts a backup from the retention
    -- policy. @False@ means the service applies the backup retention policy
    -- defined at the cluster.
    Backup -> Maybe Bool
neverExpires :: Prelude.Maybe Prelude.Bool,
    -- | The identifier (ID) of the source backup from which the new backup was
    -- copied.
    Backup -> Maybe Text
sourceBackup :: Prelude.Maybe Prelude.Text,
    -- | The identifier (ID) of the cluster containing the source backup from
    -- which the new backup was copied.
    Backup -> Maybe Text
sourceCluster :: Prelude.Maybe Prelude.Text,
    -- | The AWS Region that contains the source backup from which the new backup
    -- was copied.
    Backup -> Maybe Text
sourceRegion :: Prelude.Maybe Prelude.Text,
    -- | The list of tags for the backup.
    Backup -> Maybe [Tag]
tagList :: Prelude.Maybe [Tag],
    -- | The identifier (ID) of the backup.
    Backup -> Text
backupId :: Prelude.Text
  }
  deriving (Backup -> Backup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Backup -> Backup -> Bool
$c/= :: Backup -> Backup -> Bool
== :: Backup -> Backup -> Bool
$c== :: Backup -> Backup -> Bool
Prelude.Eq, ReadPrec [Backup]
ReadPrec Backup
Int -> ReadS Backup
ReadS [Backup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Backup]
$creadListPrec :: ReadPrec [Backup]
readPrec :: ReadPrec Backup
$creadPrec :: ReadPrec Backup
readList :: ReadS [Backup]
$creadList :: ReadS [Backup]
readsPrec :: Int -> ReadS Backup
$creadsPrec :: Int -> ReadS Backup
Prelude.Read, Int -> Backup -> ShowS
[Backup] -> ShowS
Backup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Backup] -> ShowS
$cshowList :: [Backup] -> ShowS
show :: Backup -> String
$cshow :: Backup -> String
showsPrec :: Int -> Backup -> ShowS
$cshowsPrec :: Int -> Backup -> ShowS
Prelude.Show, forall x. Rep Backup x -> Backup
forall x. Backup -> Rep Backup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Backup x -> Backup
$cfrom :: forall x. Backup -> Rep Backup x
Prelude.Generic)

-- |
-- Create a value of 'Backup' 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:
--
-- 'backupState', 'backup_backupState' - The state of the backup.
--
-- 'clusterId', 'backup_clusterId' - The identifier (ID) of the cluster that was backed up.
--
-- 'copyTimestamp', 'backup_copyTimestamp' - The date and time when the backup was copied from a source backup.
--
-- 'createTimestamp', 'backup_createTimestamp' - The date and time when the backup was created.
--
-- 'deleteTimestamp', 'backup_deleteTimestamp' - The date and time when the backup will be permanently deleted.
--
-- 'neverExpires', 'backup_neverExpires' - Specifies whether the service should exempt a backup from the retention
-- policy for the cluster. @True@ exempts a backup from the retention
-- policy. @False@ means the service applies the backup retention policy
-- defined at the cluster.
--
-- 'sourceBackup', 'backup_sourceBackup' - The identifier (ID) of the source backup from which the new backup was
-- copied.
--
-- 'sourceCluster', 'backup_sourceCluster' - The identifier (ID) of the cluster containing the source backup from
-- which the new backup was copied.
--
-- 'sourceRegion', 'backup_sourceRegion' - The AWS Region that contains the source backup from which the new backup
-- was copied.
--
-- 'tagList', 'backup_tagList' - The list of tags for the backup.
--
-- 'backupId', 'backup_backupId' - The identifier (ID) of the backup.
newBackup ::
  -- | 'backupId'
  Prelude.Text ->
  Backup
newBackup :: Text -> Backup
newBackup Text
pBackupId_ =
  Backup'
    { $sel:backupState:Backup' :: Maybe BackupState
backupState = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterId:Backup' :: Maybe Text
clusterId = forall a. Maybe a
Prelude.Nothing,
      $sel:copyTimestamp:Backup' :: Maybe POSIX
copyTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:createTimestamp:Backup' :: Maybe POSIX
createTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteTimestamp:Backup' :: Maybe POSIX
deleteTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:neverExpires:Backup' :: Maybe Bool
neverExpires = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceBackup:Backup' :: Maybe Text
sourceBackup = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceCluster:Backup' :: Maybe Text
sourceCluster = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceRegion:Backup' :: Maybe Text
sourceRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:tagList:Backup' :: Maybe [Tag]
tagList = forall a. Maybe a
Prelude.Nothing,
      $sel:backupId:Backup' :: Text
backupId = Text
pBackupId_
    }

-- | The state of the backup.
backup_backupState :: Lens.Lens' Backup (Prelude.Maybe BackupState)
backup_backupState :: Lens' Backup (Maybe BackupState)
backup_backupState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe BackupState
backupState :: Maybe BackupState
$sel:backupState:Backup' :: Backup -> Maybe BackupState
backupState} -> Maybe BackupState
backupState) (\s :: Backup
s@Backup' {} Maybe BackupState
a -> Backup
s {$sel:backupState:Backup' :: Maybe BackupState
backupState = Maybe BackupState
a} :: Backup)

-- | The identifier (ID) of the cluster that was backed up.
backup_clusterId :: Lens.Lens' Backup (Prelude.Maybe Prelude.Text)
backup_clusterId :: Lens' Backup (Maybe Text)
backup_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe Text
clusterId :: Maybe Text
$sel:clusterId:Backup' :: Backup -> Maybe Text
clusterId} -> Maybe Text
clusterId) (\s :: Backup
s@Backup' {} Maybe Text
a -> Backup
s {$sel:clusterId:Backup' :: Maybe Text
clusterId = Maybe Text
a} :: Backup)

-- | The date and time when the backup was copied from a source backup.
backup_copyTimestamp :: Lens.Lens' Backup (Prelude.Maybe Prelude.UTCTime)
backup_copyTimestamp :: Lens' Backup (Maybe UTCTime)
backup_copyTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe POSIX
copyTimestamp :: Maybe POSIX
$sel:copyTimestamp:Backup' :: Backup -> Maybe POSIX
copyTimestamp} -> Maybe POSIX
copyTimestamp) (\s :: Backup
s@Backup' {} Maybe POSIX
a -> Backup
s {$sel:copyTimestamp:Backup' :: Maybe POSIX
copyTimestamp = Maybe POSIX
a} :: Backup) 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 date and time when the backup was created.
backup_createTimestamp :: Lens.Lens' Backup (Prelude.Maybe Prelude.UTCTime)
backup_createTimestamp :: Lens' Backup (Maybe UTCTime)
backup_createTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe POSIX
createTimestamp :: Maybe POSIX
$sel:createTimestamp:Backup' :: Backup -> Maybe POSIX
createTimestamp} -> Maybe POSIX
createTimestamp) (\s :: Backup
s@Backup' {} Maybe POSIX
a -> Backup
s {$sel:createTimestamp:Backup' :: Maybe POSIX
createTimestamp = Maybe POSIX
a} :: Backup) 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 date and time when the backup will be permanently deleted.
backup_deleteTimestamp :: Lens.Lens' Backup (Prelude.Maybe Prelude.UTCTime)
backup_deleteTimestamp :: Lens' Backup (Maybe UTCTime)
backup_deleteTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe POSIX
deleteTimestamp :: Maybe POSIX
$sel:deleteTimestamp:Backup' :: Backup -> Maybe POSIX
deleteTimestamp} -> Maybe POSIX
deleteTimestamp) (\s :: Backup
s@Backup' {} Maybe POSIX
a -> Backup
s {$sel:deleteTimestamp:Backup' :: Maybe POSIX
deleteTimestamp = Maybe POSIX
a} :: Backup) 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

-- | Specifies whether the service should exempt a backup from the retention
-- policy for the cluster. @True@ exempts a backup from the retention
-- policy. @False@ means the service applies the backup retention policy
-- defined at the cluster.
backup_neverExpires :: Lens.Lens' Backup (Prelude.Maybe Prelude.Bool)
backup_neverExpires :: Lens' Backup (Maybe Bool)
backup_neverExpires = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe Bool
neverExpires :: Maybe Bool
$sel:neverExpires:Backup' :: Backup -> Maybe Bool
neverExpires} -> Maybe Bool
neverExpires) (\s :: Backup
s@Backup' {} Maybe Bool
a -> Backup
s {$sel:neverExpires:Backup' :: Maybe Bool
neverExpires = Maybe Bool
a} :: Backup)

-- | The identifier (ID) of the source backup from which the new backup was
-- copied.
backup_sourceBackup :: Lens.Lens' Backup (Prelude.Maybe Prelude.Text)
backup_sourceBackup :: Lens' Backup (Maybe Text)
backup_sourceBackup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe Text
sourceBackup :: Maybe Text
$sel:sourceBackup:Backup' :: Backup -> Maybe Text
sourceBackup} -> Maybe Text
sourceBackup) (\s :: Backup
s@Backup' {} Maybe Text
a -> Backup
s {$sel:sourceBackup:Backup' :: Maybe Text
sourceBackup = Maybe Text
a} :: Backup)

-- | The identifier (ID) of the cluster containing the source backup from
-- which the new backup was copied.
backup_sourceCluster :: Lens.Lens' Backup (Prelude.Maybe Prelude.Text)
backup_sourceCluster :: Lens' Backup (Maybe Text)
backup_sourceCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe Text
sourceCluster :: Maybe Text
$sel:sourceCluster:Backup' :: Backup -> Maybe Text
sourceCluster} -> Maybe Text
sourceCluster) (\s :: Backup
s@Backup' {} Maybe Text
a -> Backup
s {$sel:sourceCluster:Backup' :: Maybe Text
sourceCluster = Maybe Text
a} :: Backup)

-- | The AWS Region that contains the source backup from which the new backup
-- was copied.
backup_sourceRegion :: Lens.Lens' Backup (Prelude.Maybe Prelude.Text)
backup_sourceRegion :: Lens' Backup (Maybe Text)
backup_sourceRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe Text
sourceRegion :: Maybe Text
$sel:sourceRegion:Backup' :: Backup -> Maybe Text
sourceRegion} -> Maybe Text
sourceRegion) (\s :: Backup
s@Backup' {} Maybe Text
a -> Backup
s {$sel:sourceRegion:Backup' :: Maybe Text
sourceRegion = Maybe Text
a} :: Backup)

-- | The list of tags for the backup.
backup_tagList :: Lens.Lens' Backup (Prelude.Maybe [Tag])
backup_tagList :: Lens' Backup (Maybe [Tag])
backup_tagList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Maybe [Tag]
tagList :: Maybe [Tag]
$sel:tagList:Backup' :: Backup -> Maybe [Tag]
tagList} -> Maybe [Tag]
tagList) (\s :: Backup
s@Backup' {} Maybe [Tag]
a -> Backup
s {$sel:tagList:Backup' :: Maybe [Tag]
tagList = Maybe [Tag]
a} :: Backup) 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 identifier (ID) of the backup.
backup_backupId :: Lens.Lens' Backup Prelude.Text
backup_backupId :: Lens' Backup Text
backup_backupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Backup' {Text
backupId :: Text
$sel:backupId:Backup' :: Backup -> Text
backupId} -> Text
backupId) (\s :: Backup
s@Backup' {} Text
a -> Backup
s {$sel:backupId:Backup' :: Text
backupId = Text
a} :: Backup)

instance Data.FromJSON Backup where
  parseJSON :: Value -> Parser Backup
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Backup"
      ( \Object
x ->
          Maybe BackupState
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Tag]
-> Text
-> Backup
Backup'
            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
"BackupState")
            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
"ClusterId")
            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
"CopyTimestamp")
            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
"CreateTimestamp")
            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
"DeleteTimestamp")
            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
"NeverExpires")
            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
"SourceBackup")
            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
"SourceCluster")
            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
"SourceRegion")
            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
"TagList" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"BackupId")
      )

instance Prelude.Hashable Backup where
  hashWithSalt :: Int -> Backup -> Int
hashWithSalt Int
_salt Backup' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe POSIX
Maybe BackupState
Text
backupId :: Text
tagList :: Maybe [Tag]
sourceRegion :: Maybe Text
sourceCluster :: Maybe Text
sourceBackup :: Maybe Text
neverExpires :: Maybe Bool
deleteTimestamp :: Maybe POSIX
createTimestamp :: Maybe POSIX
copyTimestamp :: Maybe POSIX
clusterId :: Maybe Text
backupState :: Maybe BackupState
$sel:backupId:Backup' :: Backup -> Text
$sel:tagList:Backup' :: Backup -> Maybe [Tag]
$sel:sourceRegion:Backup' :: Backup -> Maybe Text
$sel:sourceCluster:Backup' :: Backup -> Maybe Text
$sel:sourceBackup:Backup' :: Backup -> Maybe Text
$sel:neverExpires:Backup' :: Backup -> Maybe Bool
$sel:deleteTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:createTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:copyTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:clusterId:Backup' :: Backup -> Maybe Text
$sel:backupState:Backup' :: Backup -> Maybe BackupState
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BackupState
backupState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
copyTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
deleteTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
neverExpires
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceBackup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceCluster
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tagList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
backupId

instance Prelude.NFData Backup where
  rnf :: Backup -> ()
rnf Backup' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe POSIX
Maybe BackupState
Text
backupId :: Text
tagList :: Maybe [Tag]
sourceRegion :: Maybe Text
sourceCluster :: Maybe Text
sourceBackup :: Maybe Text
neverExpires :: Maybe Bool
deleteTimestamp :: Maybe POSIX
createTimestamp :: Maybe POSIX
copyTimestamp :: Maybe POSIX
clusterId :: Maybe Text
backupState :: Maybe BackupState
$sel:backupId:Backup' :: Backup -> Text
$sel:tagList:Backup' :: Backup -> Maybe [Tag]
$sel:sourceRegion:Backup' :: Backup -> Maybe Text
$sel:sourceCluster:Backup' :: Backup -> Maybe Text
$sel:sourceBackup:Backup' :: Backup -> Maybe Text
$sel:neverExpires:Backup' :: Backup -> Maybe Bool
$sel:deleteTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:createTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:copyTimestamp:Backup' :: Backup -> Maybe POSIX
$sel:clusterId:Backup' :: Backup -> Maybe Text
$sel:backupState:Backup' :: Backup -> Maybe BackupState
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BackupState
backupState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
copyTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
deleteTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
neverExpires
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceBackup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceCluster
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tagList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
backupId