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

import Amazonka.Backup.Types.BackupJobState
import Amazonka.Backup.Types.RecoveryPointCreator
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 detailed information about a backup job.
--
-- /See:/ 'newBackupJob' smart constructor.
data BackupJob = BackupJob'
  { -- | The account ID that owns the backup job.
    BackupJob -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | Uniquely identifies a request to Backup to back up a resource.
    BackupJob -> Maybe Text
backupJobId :: Prelude.Maybe Prelude.Text,
    -- | Specifies the backup option for a selected resource. This option is only
    -- available for Windows Volume Shadow Copy Service (VSS) backup jobs.
    --
    -- Valid values: Set to @\"WindowsVSS\":\"enabled\"@ to enable the
    -- @WindowsVSS@ backup option and create a Windows VSS backup. Set to
    -- @\"WindowsVSS\":\"disabled\"@ to create a regular backup. If you specify
    -- an invalid option, you get an @InvalidParameterValueException@
    -- exception.
    BackupJob -> Maybe (HashMap Text Text)
backupOptions :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The size, in bytes, of a backup.
    BackupJob -> Maybe Integer
backupSizeInBytes :: Prelude.Maybe Prelude.Integer,
    -- | Represents the type of backup for a backup job.
    BackupJob -> Maybe Text
backupType :: Prelude.Maybe Prelude.Text,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a backup vault;
    -- for example, @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
    BackupJob -> Maybe Text
backupVaultArn :: Prelude.Maybe Prelude.Text,
    -- | The name of a logical container where backups are stored. Backup vaults
    -- are identified by names that are unique to the account used to create
    -- them and the Amazon Web Services Region where they are created. They
    -- consist of lowercase letters, numbers, and hyphens.
    BackupJob -> Maybe Text
backupVaultName :: Prelude.Maybe Prelude.Text,
    -- | The size in bytes transferred to a backup vault at the time that the job
    -- status was queried.
    BackupJob -> Maybe Integer
bytesTransferred :: Prelude.Maybe Prelude.Integer,
    -- | The date and time a job to create a backup job is completed, in Unix
    -- format and Coordinated Universal Time (UTC). The value of
    -- @CompletionDate@ is accurate to milliseconds. For example, the value
    -- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
    BackupJob -> Maybe POSIX
completionDate :: Prelude.Maybe Data.POSIX,
    -- | Contains identifying information about the creation of a backup job,
    -- including the @BackupPlanArn@, @BackupPlanId@, @BackupPlanVersion@, and
    -- @BackupRuleId@ of the backup plan used to create it.
    BackupJob -> Maybe RecoveryPointCreator
createdBy :: Prelude.Maybe RecoveryPointCreator,
    -- | The date and time a backup job is created, in Unix format and
    -- Coordinated Universal Time (UTC). The value of @CreationDate@ is
    -- accurate to milliseconds. For example, the value 1516925490.087
    -- represents Friday, January 26, 2018 12:11:30.087 AM.
    BackupJob -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | The date and time a job to back up resources is expected to be
    -- completed, in Unix format and Coordinated Universal Time (UTC). The
    -- value of @ExpectedCompletionDate@ is accurate to milliseconds. For
    -- example, the value 1516925490.087 represents Friday, January 26, 2018
    -- 12:11:30.087 AM.
    BackupJob -> Maybe POSIX
expectedCompletionDate :: Prelude.Maybe Data.POSIX,
    -- | Specifies the IAM role ARN used to create the target recovery point. IAM
    -- roles other than the default role must include either @AWSBackup@ or
    -- @AwsBackup@ in the role name. For example,
    -- @arn:aws:iam::123456789012:role\/AWSBackupRDSAccess@. Role names without
    -- those strings lack permissions to perform backup jobs.
    BackupJob -> Maybe Text
iamRoleArn :: Prelude.Maybe Prelude.Text,
    -- | This is a boolean value indicating this is a parent (composite) backup
    -- job.
    BackupJob -> Maybe Bool
isParent :: Prelude.Maybe Prelude.Bool,
    -- | This uniquely identifies a request to Backup to back up a resource. The
    -- return will be the parent (composite) job ID.
    BackupJob -> Maybe Text
parentJobId :: Prelude.Maybe Prelude.Text,
    -- | Contains an estimated percentage complete of a job at the time the job
    -- status was queried.
    BackupJob -> Maybe Text
percentDone :: Prelude.Maybe Prelude.Text,
    -- | An ARN that uniquely identifies a recovery point; for example,
    -- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
    BackupJob -> Maybe Text
recoveryPointArn :: Prelude.Maybe Prelude.Text,
    -- | An ARN that uniquely identifies a resource. The format of the ARN
    -- depends on the resource type.
    BackupJob -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | The type of Amazon Web Services resource to be backed up; for example,
    -- an Amazon Elastic Block Store (Amazon EBS) volume or an Amazon
    -- Relational Database Service (Amazon RDS) database. For Windows Volume
    -- Shadow Copy Service (VSS) backups, the only supported resource type is
    -- Amazon EC2.
    BackupJob -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | Specifies the time in Unix format and Coordinated Universal Time (UTC)
    -- when a backup job must be started before it is canceled. The value is
    -- calculated by adding the start window to the scheduled time. So if the
    -- scheduled time were 6:00 PM and the start window is 2 hours, the
    -- @StartBy@ time would be 8:00 PM on the date specified. The value of
    -- @StartBy@ is accurate to milliseconds. For example, the value
    -- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
    BackupJob -> Maybe POSIX
startBy :: Prelude.Maybe Data.POSIX,
    -- | The current state of a resource recovery point.
    BackupJob -> Maybe BackupJobState
state :: Prelude.Maybe BackupJobState,
    -- | A detailed message explaining the status of the job to back up a
    -- resource.
    BackupJob -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text
  }
  deriving (BackupJob -> BackupJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BackupJob -> BackupJob -> Bool
$c/= :: BackupJob -> BackupJob -> Bool
== :: BackupJob -> BackupJob -> Bool
$c== :: BackupJob -> BackupJob -> Bool
Prelude.Eq, ReadPrec [BackupJob]
ReadPrec BackupJob
Int -> ReadS BackupJob
ReadS [BackupJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BackupJob]
$creadListPrec :: ReadPrec [BackupJob]
readPrec :: ReadPrec BackupJob
$creadPrec :: ReadPrec BackupJob
readList :: ReadS [BackupJob]
$creadList :: ReadS [BackupJob]
readsPrec :: Int -> ReadS BackupJob
$creadsPrec :: Int -> ReadS BackupJob
Prelude.Read, Int -> BackupJob -> ShowS
[BackupJob] -> ShowS
BackupJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackupJob] -> ShowS
$cshowList :: [BackupJob] -> ShowS
show :: BackupJob -> String
$cshow :: BackupJob -> String
showsPrec :: Int -> BackupJob -> ShowS
$cshowsPrec :: Int -> BackupJob -> ShowS
Prelude.Show, forall x. Rep BackupJob x -> BackupJob
forall x. BackupJob -> Rep BackupJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BackupJob x -> BackupJob
$cfrom :: forall x. BackupJob -> Rep BackupJob x
Prelude.Generic)

-- |
-- Create a value of 'BackupJob' 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:
--
-- 'accountId', 'backupJob_accountId' - The account ID that owns the backup job.
--
-- 'backupJobId', 'backupJob_backupJobId' - Uniquely identifies a request to Backup to back up a resource.
--
-- 'backupOptions', 'backupJob_backupOptions' - Specifies the backup option for a selected resource. This option is only
-- available for Windows Volume Shadow Copy Service (VSS) backup jobs.
--
-- Valid values: Set to @\"WindowsVSS\":\"enabled\"@ to enable the
-- @WindowsVSS@ backup option and create a Windows VSS backup. Set to
-- @\"WindowsVSS\":\"disabled\"@ to create a regular backup. If you specify
-- an invalid option, you get an @InvalidParameterValueException@
-- exception.
--
-- 'backupSizeInBytes', 'backupJob_backupSizeInBytes' - The size, in bytes, of a backup.
--
-- 'backupType', 'backupJob_backupType' - Represents the type of backup for a backup job.
--
-- 'backupVaultArn', 'backupJob_backupVaultArn' - An Amazon Resource Name (ARN) that uniquely identifies a backup vault;
-- for example, @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
--
-- 'backupVaultName', 'backupJob_backupVaultName' - The name of a logical container where backups are stored. Backup vaults
-- are identified by names that are unique to the account used to create
-- them and the Amazon Web Services Region where they are created. They
-- consist of lowercase letters, numbers, and hyphens.
--
-- 'bytesTransferred', 'backupJob_bytesTransferred' - The size in bytes transferred to a backup vault at the time that the job
-- status was queried.
--
-- 'completionDate', 'backupJob_completionDate' - The date and time a job to create a backup job is completed, in Unix
-- format and Coordinated Universal Time (UTC). The value of
-- @CompletionDate@ is accurate to milliseconds. For example, the value
-- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'createdBy', 'backupJob_createdBy' - Contains identifying information about the creation of a backup job,
-- including the @BackupPlanArn@, @BackupPlanId@, @BackupPlanVersion@, and
-- @BackupRuleId@ of the backup plan used to create it.
--
-- 'creationDate', 'backupJob_creationDate' - The date and time a backup job is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationDate@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'expectedCompletionDate', 'backupJob_expectedCompletionDate' - The date and time a job to back up resources is expected to be
-- completed, in Unix format and Coordinated Universal Time (UTC). The
-- value of @ExpectedCompletionDate@ is accurate to milliseconds. For
-- example, the value 1516925490.087 represents Friday, January 26, 2018
-- 12:11:30.087 AM.
--
-- 'iamRoleArn', 'backupJob_iamRoleArn' - Specifies the IAM role ARN used to create the target recovery point. IAM
-- roles other than the default role must include either @AWSBackup@ or
-- @AwsBackup@ in the role name. For example,
-- @arn:aws:iam::123456789012:role\/AWSBackupRDSAccess@. Role names without
-- those strings lack permissions to perform backup jobs.
--
-- 'isParent', 'backupJob_isParent' - This is a boolean value indicating this is a parent (composite) backup
-- job.
--
-- 'parentJobId', 'backupJob_parentJobId' - This uniquely identifies a request to Backup to back up a resource. The
-- return will be the parent (composite) job ID.
--
-- 'percentDone', 'backupJob_percentDone' - Contains an estimated percentage complete of a job at the time the job
-- status was queried.
--
-- 'recoveryPointArn', 'backupJob_recoveryPointArn' - An ARN that uniquely identifies a recovery point; for example,
-- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
--
-- 'resourceArn', 'backupJob_resourceArn' - An ARN that uniquely identifies a resource. The format of the ARN
-- depends on the resource type.
--
-- 'resourceType', 'backupJob_resourceType' - The type of Amazon Web Services resource to be backed up; for example,
-- an Amazon Elastic Block Store (Amazon EBS) volume or an Amazon
-- Relational Database Service (Amazon RDS) database. For Windows Volume
-- Shadow Copy Service (VSS) backups, the only supported resource type is
-- Amazon EC2.
--
-- 'startBy', 'backupJob_startBy' - Specifies the time in Unix format and Coordinated Universal Time (UTC)
-- when a backup job must be started before it is canceled. The value is
-- calculated by adding the start window to the scheduled time. So if the
-- scheduled time were 6:00 PM and the start window is 2 hours, the
-- @StartBy@ time would be 8:00 PM on the date specified. The value of
-- @StartBy@ is accurate to milliseconds. For example, the value
-- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'state', 'backupJob_state' - The current state of a resource recovery point.
--
-- 'statusMessage', 'backupJob_statusMessage' - A detailed message explaining the status of the job to back up a
-- resource.
newBackupJob ::
  BackupJob
newBackupJob :: BackupJob
newBackupJob =
  BackupJob'
    { $sel:accountId:BackupJob' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:backupJobId:BackupJob' :: Maybe Text
backupJobId = forall a. Maybe a
Prelude.Nothing,
      $sel:backupOptions:BackupJob' :: Maybe (HashMap Text Text)
backupOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:backupSizeInBytes:BackupJob' :: Maybe Integer
backupSizeInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:backupType:BackupJob' :: Maybe Text
backupType = forall a. Maybe a
Prelude.Nothing,
      $sel:backupVaultArn:BackupJob' :: Maybe Text
backupVaultArn = forall a. Maybe a
Prelude.Nothing,
      $sel:backupVaultName:BackupJob' :: Maybe Text
backupVaultName = forall a. Maybe a
Prelude.Nothing,
      $sel:bytesTransferred:BackupJob' :: Maybe Integer
bytesTransferred = forall a. Maybe a
Prelude.Nothing,
      $sel:completionDate:BackupJob' :: Maybe POSIX
completionDate = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:BackupJob' :: Maybe RecoveryPointCreator
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:BackupJob' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedCompletionDate:BackupJob' :: Maybe POSIX
expectedCompletionDate = forall a. Maybe a
Prelude.Nothing,
      $sel:iamRoleArn:BackupJob' :: Maybe Text
iamRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:isParent:BackupJob' :: Maybe Bool
isParent = forall a. Maybe a
Prelude.Nothing,
      $sel:parentJobId:BackupJob' :: Maybe Text
parentJobId = forall a. Maybe a
Prelude.Nothing,
      $sel:percentDone:BackupJob' :: Maybe Text
percentDone = forall a. Maybe a
Prelude.Nothing,
      $sel:recoveryPointArn:BackupJob' :: Maybe Text
recoveryPointArn = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:BackupJob' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:BackupJob' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:startBy:BackupJob' :: Maybe POSIX
startBy = forall a. Maybe a
Prelude.Nothing,
      $sel:state:BackupJob' :: Maybe BackupJobState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:BackupJob' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing
    }

-- | The account ID that owns the backup job.
backupJob_accountId :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_accountId :: Lens' BackupJob (Maybe Text)
backupJob_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
accountId :: Maybe Text
$sel:accountId:BackupJob' :: BackupJob -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:accountId:BackupJob' :: Maybe Text
accountId = Maybe Text
a} :: BackupJob)

-- | Uniquely identifies a request to Backup to back up a resource.
backupJob_backupJobId :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_backupJobId :: Lens' BackupJob (Maybe Text)
backupJob_backupJobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
backupJobId :: Maybe Text
$sel:backupJobId:BackupJob' :: BackupJob -> Maybe Text
backupJobId} -> Maybe Text
backupJobId) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:backupJobId:BackupJob' :: Maybe Text
backupJobId = Maybe Text
a} :: BackupJob)

-- | Specifies the backup option for a selected resource. This option is only
-- available for Windows Volume Shadow Copy Service (VSS) backup jobs.
--
-- Valid values: Set to @\"WindowsVSS\":\"enabled\"@ to enable the
-- @WindowsVSS@ backup option and create a Windows VSS backup. Set to
-- @\"WindowsVSS\":\"disabled\"@ to create a regular backup. If you specify
-- an invalid option, you get an @InvalidParameterValueException@
-- exception.
backupJob_backupOptions :: Lens.Lens' BackupJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
backupJob_backupOptions :: Lens' BackupJob (Maybe (HashMap Text Text))
backupJob_backupOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe (HashMap Text Text)
backupOptions :: Maybe (HashMap Text Text)
$sel:backupOptions:BackupJob' :: BackupJob -> Maybe (HashMap Text Text)
backupOptions} -> Maybe (HashMap Text Text)
backupOptions) (\s :: BackupJob
s@BackupJob' {} Maybe (HashMap Text Text)
a -> BackupJob
s {$sel:backupOptions:BackupJob' :: Maybe (HashMap Text Text)
backupOptions = Maybe (HashMap Text Text)
a} :: BackupJob) 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 size, in bytes, of a backup.
backupJob_backupSizeInBytes :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Integer)
backupJob_backupSizeInBytes :: Lens' BackupJob (Maybe Integer)
backupJob_backupSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Integer
backupSizeInBytes :: Maybe Integer
$sel:backupSizeInBytes:BackupJob' :: BackupJob -> Maybe Integer
backupSizeInBytes} -> Maybe Integer
backupSizeInBytes) (\s :: BackupJob
s@BackupJob' {} Maybe Integer
a -> BackupJob
s {$sel:backupSizeInBytes:BackupJob' :: Maybe Integer
backupSizeInBytes = Maybe Integer
a} :: BackupJob)

-- | Represents the type of backup for a backup job.
backupJob_backupType :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_backupType :: Lens' BackupJob (Maybe Text)
backupJob_backupType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
backupType :: Maybe Text
$sel:backupType:BackupJob' :: BackupJob -> Maybe Text
backupType} -> Maybe Text
backupType) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:backupType:BackupJob' :: Maybe Text
backupType = Maybe Text
a} :: BackupJob)

-- | An Amazon Resource Name (ARN) that uniquely identifies a backup vault;
-- for example, @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
backupJob_backupVaultArn :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_backupVaultArn :: Lens' BackupJob (Maybe Text)
backupJob_backupVaultArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
backupVaultArn :: Maybe Text
$sel:backupVaultArn:BackupJob' :: BackupJob -> Maybe Text
backupVaultArn} -> Maybe Text
backupVaultArn) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:backupVaultArn:BackupJob' :: Maybe Text
backupVaultArn = Maybe Text
a} :: BackupJob)

-- | The name of a logical container where backups are stored. Backup vaults
-- are identified by names that are unique to the account used to create
-- them and the Amazon Web Services Region where they are created. They
-- consist of lowercase letters, numbers, and hyphens.
backupJob_backupVaultName :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_backupVaultName :: Lens' BackupJob (Maybe Text)
backupJob_backupVaultName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
backupVaultName :: Maybe Text
$sel:backupVaultName:BackupJob' :: BackupJob -> Maybe Text
backupVaultName} -> Maybe Text
backupVaultName) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:backupVaultName:BackupJob' :: Maybe Text
backupVaultName = Maybe Text
a} :: BackupJob)

-- | The size in bytes transferred to a backup vault at the time that the job
-- status was queried.
backupJob_bytesTransferred :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Integer)
backupJob_bytesTransferred :: Lens' BackupJob (Maybe Integer)
backupJob_bytesTransferred = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Integer
bytesTransferred :: Maybe Integer
$sel:bytesTransferred:BackupJob' :: BackupJob -> Maybe Integer
bytesTransferred} -> Maybe Integer
bytesTransferred) (\s :: BackupJob
s@BackupJob' {} Maybe Integer
a -> BackupJob
s {$sel:bytesTransferred:BackupJob' :: Maybe Integer
bytesTransferred = Maybe Integer
a} :: BackupJob)

-- | The date and time a job to create a backup job is completed, in Unix
-- format and Coordinated Universal Time (UTC). The value of
-- @CompletionDate@ is accurate to milliseconds. For example, the value
-- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
backupJob_completionDate :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.UTCTime)
backupJob_completionDate :: Lens' BackupJob (Maybe UTCTime)
backupJob_completionDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe POSIX
completionDate :: Maybe POSIX
$sel:completionDate:BackupJob' :: BackupJob -> Maybe POSIX
completionDate} -> Maybe POSIX
completionDate) (\s :: BackupJob
s@BackupJob' {} Maybe POSIX
a -> BackupJob
s {$sel:completionDate:BackupJob' :: Maybe POSIX
completionDate = Maybe POSIX
a} :: BackupJob) 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

-- | Contains identifying information about the creation of a backup job,
-- including the @BackupPlanArn@, @BackupPlanId@, @BackupPlanVersion@, and
-- @BackupRuleId@ of the backup plan used to create it.
backupJob_createdBy :: Lens.Lens' BackupJob (Prelude.Maybe RecoveryPointCreator)
backupJob_createdBy :: Lens' BackupJob (Maybe RecoveryPointCreator)
backupJob_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe RecoveryPointCreator
createdBy :: Maybe RecoveryPointCreator
$sel:createdBy:BackupJob' :: BackupJob -> Maybe RecoveryPointCreator
createdBy} -> Maybe RecoveryPointCreator
createdBy) (\s :: BackupJob
s@BackupJob' {} Maybe RecoveryPointCreator
a -> BackupJob
s {$sel:createdBy:BackupJob' :: Maybe RecoveryPointCreator
createdBy = Maybe RecoveryPointCreator
a} :: BackupJob)

-- | The date and time a backup job is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationDate@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
backupJob_creationDate :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.UTCTime)
backupJob_creationDate :: Lens' BackupJob (Maybe UTCTime)
backupJob_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:BackupJob' :: BackupJob -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: BackupJob
s@BackupJob' {} Maybe POSIX
a -> BackupJob
s {$sel:creationDate:BackupJob' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: BackupJob) 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 a job to back up resources is expected to be
-- completed, in Unix format and Coordinated Universal Time (UTC). The
-- value of @ExpectedCompletionDate@ is accurate to milliseconds. For
-- example, the value 1516925490.087 represents Friday, January 26, 2018
-- 12:11:30.087 AM.
backupJob_expectedCompletionDate :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.UTCTime)
backupJob_expectedCompletionDate :: Lens' BackupJob (Maybe UTCTime)
backupJob_expectedCompletionDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe POSIX
expectedCompletionDate :: Maybe POSIX
$sel:expectedCompletionDate:BackupJob' :: BackupJob -> Maybe POSIX
expectedCompletionDate} -> Maybe POSIX
expectedCompletionDate) (\s :: BackupJob
s@BackupJob' {} Maybe POSIX
a -> BackupJob
s {$sel:expectedCompletionDate:BackupJob' :: Maybe POSIX
expectedCompletionDate = Maybe POSIX
a} :: BackupJob) 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 the IAM role ARN used to create the target recovery point. IAM
-- roles other than the default role must include either @AWSBackup@ or
-- @AwsBackup@ in the role name. For example,
-- @arn:aws:iam::123456789012:role\/AWSBackupRDSAccess@. Role names without
-- those strings lack permissions to perform backup jobs.
backupJob_iamRoleArn :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_iamRoleArn :: Lens' BackupJob (Maybe Text)
backupJob_iamRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
iamRoleArn :: Maybe Text
$sel:iamRoleArn:BackupJob' :: BackupJob -> Maybe Text
iamRoleArn} -> Maybe Text
iamRoleArn) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:iamRoleArn:BackupJob' :: Maybe Text
iamRoleArn = Maybe Text
a} :: BackupJob)

-- | This is a boolean value indicating this is a parent (composite) backup
-- job.
backupJob_isParent :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Bool)
backupJob_isParent :: Lens' BackupJob (Maybe Bool)
backupJob_isParent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Bool
isParent :: Maybe Bool
$sel:isParent:BackupJob' :: BackupJob -> Maybe Bool
isParent} -> Maybe Bool
isParent) (\s :: BackupJob
s@BackupJob' {} Maybe Bool
a -> BackupJob
s {$sel:isParent:BackupJob' :: Maybe Bool
isParent = Maybe Bool
a} :: BackupJob)

-- | This uniquely identifies a request to Backup to back up a resource. The
-- return will be the parent (composite) job ID.
backupJob_parentJobId :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_parentJobId :: Lens' BackupJob (Maybe Text)
backupJob_parentJobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
parentJobId :: Maybe Text
$sel:parentJobId:BackupJob' :: BackupJob -> Maybe Text
parentJobId} -> Maybe Text
parentJobId) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:parentJobId:BackupJob' :: Maybe Text
parentJobId = Maybe Text
a} :: BackupJob)

-- | Contains an estimated percentage complete of a job at the time the job
-- status was queried.
backupJob_percentDone :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_percentDone :: Lens' BackupJob (Maybe Text)
backupJob_percentDone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
percentDone :: Maybe Text
$sel:percentDone:BackupJob' :: BackupJob -> Maybe Text
percentDone} -> Maybe Text
percentDone) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:percentDone:BackupJob' :: Maybe Text
percentDone = Maybe Text
a} :: BackupJob)

-- | An ARN that uniquely identifies a recovery point; for example,
-- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
backupJob_recoveryPointArn :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_recoveryPointArn :: Lens' BackupJob (Maybe Text)
backupJob_recoveryPointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
recoveryPointArn :: Maybe Text
$sel:recoveryPointArn:BackupJob' :: BackupJob -> Maybe Text
recoveryPointArn} -> Maybe Text
recoveryPointArn) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:recoveryPointArn:BackupJob' :: Maybe Text
recoveryPointArn = Maybe Text
a} :: BackupJob)

-- | An ARN that uniquely identifies a resource. The format of the ARN
-- depends on the resource type.
backupJob_resourceArn :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_resourceArn :: Lens' BackupJob (Maybe Text)
backupJob_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:BackupJob' :: BackupJob -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:resourceArn:BackupJob' :: Maybe Text
resourceArn = Maybe Text
a} :: BackupJob)

-- | The type of Amazon Web Services resource to be backed up; for example,
-- an Amazon Elastic Block Store (Amazon EBS) volume or an Amazon
-- Relational Database Service (Amazon RDS) database. For Windows Volume
-- Shadow Copy Service (VSS) backups, the only supported resource type is
-- Amazon EC2.
backupJob_resourceType :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_resourceType :: Lens' BackupJob (Maybe Text)
backupJob_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:BackupJob' :: BackupJob -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:resourceType:BackupJob' :: Maybe Text
resourceType = Maybe Text
a} :: BackupJob)

-- | Specifies the time in Unix format and Coordinated Universal Time (UTC)
-- when a backup job must be started before it is canceled. The value is
-- calculated by adding the start window to the scheduled time. So if the
-- scheduled time were 6:00 PM and the start window is 2 hours, the
-- @StartBy@ time would be 8:00 PM on the date specified. The value of
-- @StartBy@ is accurate to milliseconds. For example, the value
-- 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
backupJob_startBy :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.UTCTime)
backupJob_startBy :: Lens' BackupJob (Maybe UTCTime)
backupJob_startBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe POSIX
startBy :: Maybe POSIX
$sel:startBy:BackupJob' :: BackupJob -> Maybe POSIX
startBy} -> Maybe POSIX
startBy) (\s :: BackupJob
s@BackupJob' {} Maybe POSIX
a -> BackupJob
s {$sel:startBy:BackupJob' :: Maybe POSIX
startBy = Maybe POSIX
a} :: BackupJob) 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 current state of a resource recovery point.
backupJob_state :: Lens.Lens' BackupJob (Prelude.Maybe BackupJobState)
backupJob_state :: Lens' BackupJob (Maybe BackupJobState)
backupJob_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe BackupJobState
state :: Maybe BackupJobState
$sel:state:BackupJob' :: BackupJob -> Maybe BackupJobState
state} -> Maybe BackupJobState
state) (\s :: BackupJob
s@BackupJob' {} Maybe BackupJobState
a -> BackupJob
s {$sel:state:BackupJob' :: Maybe BackupJobState
state = Maybe BackupJobState
a} :: BackupJob)

-- | A detailed message explaining the status of the job to back up a
-- resource.
backupJob_statusMessage :: Lens.Lens' BackupJob (Prelude.Maybe Prelude.Text)
backupJob_statusMessage :: Lens' BackupJob (Maybe Text)
backupJob_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackupJob' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:BackupJob' :: BackupJob -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: BackupJob
s@BackupJob' {} Maybe Text
a -> BackupJob
s {$sel:statusMessage:BackupJob' :: Maybe Text
statusMessage = Maybe Text
a} :: BackupJob)

instance Data.FromJSON BackupJob where
  parseJSON :: Value -> Parser BackupJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"BackupJob"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Integer
-> Maybe POSIX
-> Maybe RecoveryPointCreator
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe BackupJobState
-> Maybe Text
-> BackupJob
BackupJob'
            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
"AccountId")
            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
"BackupJobId")
            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
"BackupOptions" 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 (Maybe a)
Data..:? Key
"BackupSizeInBytes")
            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
"BackupType")
            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
"BackupVaultArn")
            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
"BackupVaultName")
            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
"BytesTransferred")
            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
"CompletionDate")
            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
"CreatedBy")
            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
"CreationDate")
            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
"ExpectedCompletionDate")
            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
"IamRoleArn")
            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
"IsParent")
            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
"ParentJobId")
            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
"PercentDone")
            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
"RecoveryPointArn")
            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
"ResourceArn")
            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
"ResourceType")
            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
"StartBy")
            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
"State")
            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
"StatusMessage")
      )

instance Prelude.Hashable BackupJob where
  hashWithSalt :: Int -> BackupJob -> Int
hashWithSalt Int
_salt BackupJob' {Maybe Bool
Maybe Integer
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe BackupJobState
Maybe RecoveryPointCreator
statusMessage :: Maybe Text
state :: Maybe BackupJobState
startBy :: Maybe POSIX
resourceType :: Maybe Text
resourceArn :: Maybe Text
recoveryPointArn :: Maybe Text
percentDone :: Maybe Text
parentJobId :: Maybe Text
isParent :: Maybe Bool
iamRoleArn :: Maybe Text
expectedCompletionDate :: Maybe POSIX
creationDate :: Maybe POSIX
createdBy :: Maybe RecoveryPointCreator
completionDate :: Maybe POSIX
bytesTransferred :: Maybe Integer
backupVaultName :: Maybe Text
backupVaultArn :: Maybe Text
backupType :: Maybe Text
backupSizeInBytes :: Maybe Integer
backupOptions :: Maybe (HashMap Text Text)
backupJobId :: Maybe Text
accountId :: Maybe Text
$sel:statusMessage:BackupJob' :: BackupJob -> Maybe Text
$sel:state:BackupJob' :: BackupJob -> Maybe BackupJobState
$sel:startBy:BackupJob' :: BackupJob -> Maybe POSIX
$sel:resourceType:BackupJob' :: BackupJob -> Maybe Text
$sel:resourceArn:BackupJob' :: BackupJob -> Maybe Text
$sel:recoveryPointArn:BackupJob' :: BackupJob -> Maybe Text
$sel:percentDone:BackupJob' :: BackupJob -> Maybe Text
$sel:parentJobId:BackupJob' :: BackupJob -> Maybe Text
$sel:isParent:BackupJob' :: BackupJob -> Maybe Bool
$sel:iamRoleArn:BackupJob' :: BackupJob -> Maybe Text
$sel:expectedCompletionDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:creationDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:createdBy:BackupJob' :: BackupJob -> Maybe RecoveryPointCreator
$sel:completionDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:bytesTransferred:BackupJob' :: BackupJob -> Maybe Integer
$sel:backupVaultName:BackupJob' :: BackupJob -> Maybe Text
$sel:backupVaultArn:BackupJob' :: BackupJob -> Maybe Text
$sel:backupType:BackupJob' :: BackupJob -> Maybe Text
$sel:backupSizeInBytes:BackupJob' :: BackupJob -> Maybe Integer
$sel:backupOptions:BackupJob' :: BackupJob -> Maybe (HashMap Text Text)
$sel:backupJobId:BackupJob' :: BackupJob -> Maybe Text
$sel:accountId:BackupJob' :: BackupJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backupJobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
backupOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
backupSizeInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backupType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backupVaultArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backupVaultName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
bytesTransferred
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
completionDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RecoveryPointCreator
createdBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
expectedCompletionDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
iamRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isParent
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parentJobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
percentDone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recoveryPointArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BackupJobState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusMessage

instance Prelude.NFData BackupJob where
  rnf :: BackupJob -> ()
rnf BackupJob' {Maybe Bool
Maybe Integer
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe BackupJobState
Maybe RecoveryPointCreator
statusMessage :: Maybe Text
state :: Maybe BackupJobState
startBy :: Maybe POSIX
resourceType :: Maybe Text
resourceArn :: Maybe Text
recoveryPointArn :: Maybe Text
percentDone :: Maybe Text
parentJobId :: Maybe Text
isParent :: Maybe Bool
iamRoleArn :: Maybe Text
expectedCompletionDate :: Maybe POSIX
creationDate :: Maybe POSIX
createdBy :: Maybe RecoveryPointCreator
completionDate :: Maybe POSIX
bytesTransferred :: Maybe Integer
backupVaultName :: Maybe Text
backupVaultArn :: Maybe Text
backupType :: Maybe Text
backupSizeInBytes :: Maybe Integer
backupOptions :: Maybe (HashMap Text Text)
backupJobId :: Maybe Text
accountId :: Maybe Text
$sel:statusMessage:BackupJob' :: BackupJob -> Maybe Text
$sel:state:BackupJob' :: BackupJob -> Maybe BackupJobState
$sel:startBy:BackupJob' :: BackupJob -> Maybe POSIX
$sel:resourceType:BackupJob' :: BackupJob -> Maybe Text
$sel:resourceArn:BackupJob' :: BackupJob -> Maybe Text
$sel:recoveryPointArn:BackupJob' :: BackupJob -> Maybe Text
$sel:percentDone:BackupJob' :: BackupJob -> Maybe Text
$sel:parentJobId:BackupJob' :: BackupJob -> Maybe Text
$sel:isParent:BackupJob' :: BackupJob -> Maybe Bool
$sel:iamRoleArn:BackupJob' :: BackupJob -> Maybe Text
$sel:expectedCompletionDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:creationDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:createdBy:BackupJob' :: BackupJob -> Maybe RecoveryPointCreator
$sel:completionDate:BackupJob' :: BackupJob -> Maybe POSIX
$sel:bytesTransferred:BackupJob' :: BackupJob -> Maybe Integer
$sel:backupVaultName:BackupJob' :: BackupJob -> Maybe Text
$sel:backupVaultArn:BackupJob' :: BackupJob -> Maybe Text
$sel:backupType:BackupJob' :: BackupJob -> Maybe Text
$sel:backupSizeInBytes:BackupJob' :: BackupJob -> Maybe Integer
$sel:backupOptions:BackupJob' :: BackupJob -> Maybe (HashMap Text Text)
$sel:backupJobId:BackupJob' :: BackupJob -> Maybe Text
$sel:accountId:BackupJob' :: BackupJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupJobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
backupOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
backupSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupVaultArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupVaultName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
bytesTransferred
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completionDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecoveryPointCreator
createdBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
expectedCompletionDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
iamRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isParent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parentJobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
percentDone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recoveryPointArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BackupJobState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusMessage