{-# 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.CopyJob
-- 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.CopyJob where

import Amazonka.Backup.Types.CopyJobState
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 copy job.
--
-- /See:/ 'newCopyJob' smart constructor.
data CopyJob = CopyJob'
  { -- | The account ID that owns the copy job.
    CopyJob -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | The size, in bytes, of a copy job.
    CopyJob -> Maybe Integer
backupSizeInBytes :: Prelude.Maybe Prelude.Integer,
    -- | This returns the statistics of the included child (nested) copy jobs.
    CopyJob -> Maybe (HashMap CopyJobState Integer)
childJobsInState :: Prelude.Maybe (Prelude.HashMap CopyJobState Prelude.Integer),
    -- | The date and time a copy 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.
    CopyJob -> Maybe POSIX
completionDate :: Prelude.Maybe Data.POSIX,
    -- | This is the identifier of a resource within a composite group, such as
    -- nested (child) recovery point belonging to a composite (parent) stack.
    -- The ID is transferred from the
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/resources-section-structure.html#resources-section-structure-syntax logical ID>
    -- within a stack.
    CopyJob -> Maybe Text
compositeMemberIdentifier :: Prelude.Maybe Prelude.Text,
    -- | Uniquely identifies a copy job.
    CopyJob -> Maybe Text
copyJobId :: Prelude.Maybe Prelude.Text,
    CopyJob -> Maybe RecoveryPointCreator
createdBy :: Prelude.Maybe RecoveryPointCreator,
    -- | The date and time a copy 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.
    CopyJob -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a destination
    -- copy vault; for example,
    -- @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
    CopyJob -> Maybe Text
destinationBackupVaultArn :: Prelude.Maybe Prelude.Text,
    -- | An ARN that uniquely identifies a destination recovery point; for
    -- example,
    -- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
    CopyJob -> Maybe Text
destinationRecoveryPointArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies the IAM role ARN used to copy the target recovery point; for
    -- example, @arn:aws:iam::123456789012:role\/S3Access@.
    CopyJob -> Maybe Text
iamRoleArn :: Prelude.Maybe Prelude.Text,
    -- | This is a boolean value indicating this is a parent (composite) copy
    -- job.
    CopyJob -> Maybe Bool
isParent :: Prelude.Maybe Prelude.Bool,
    -- | This is the number of child (nested) copy jobs.
    CopyJob -> Maybe Integer
numberOfChildJobs :: Prelude.Maybe Prelude.Integer,
    -- | This uniquely identifies a request to Backup to copy a resource. The
    -- return will be the parent (composite) job ID.
    CopyJob -> Maybe Text
parentJobId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services resource to be copied; for example, an Amazon
    -- Elastic Block Store (Amazon EBS) volume or an Amazon Relational Database
    -- Service (Amazon RDS) database.
    CopyJob -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | The type of Amazon Web Services resource to be copied; for example, an
    -- Amazon Elastic Block Store (Amazon EBS) volume or an Amazon Relational
    -- Database Service (Amazon RDS) database.
    CopyJob -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a source copy
    -- vault; for example,
    -- @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
    CopyJob -> Maybe Text
sourceBackupVaultArn :: Prelude.Maybe Prelude.Text,
    -- | An ARN that uniquely identifies a source recovery point; for example,
    -- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
    CopyJob -> Maybe Text
sourceRecoveryPointArn :: Prelude.Maybe Prelude.Text,
    -- | The current state of a copy job.
    CopyJob -> Maybe CopyJobState
state :: Prelude.Maybe CopyJobState,
    -- | A detailed message explaining the status of the job to copy a resource.
    CopyJob -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text
  }
  deriving (CopyJob -> CopyJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyJob -> CopyJob -> Bool
$c/= :: CopyJob -> CopyJob -> Bool
== :: CopyJob -> CopyJob -> Bool
$c== :: CopyJob -> CopyJob -> Bool
Prelude.Eq, ReadPrec [CopyJob]
ReadPrec CopyJob
Int -> ReadS CopyJob
ReadS [CopyJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CopyJob]
$creadListPrec :: ReadPrec [CopyJob]
readPrec :: ReadPrec CopyJob
$creadPrec :: ReadPrec CopyJob
readList :: ReadS [CopyJob]
$creadList :: ReadS [CopyJob]
readsPrec :: Int -> ReadS CopyJob
$creadsPrec :: Int -> ReadS CopyJob
Prelude.Read, Int -> CopyJob -> ShowS
[CopyJob] -> ShowS
CopyJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyJob] -> ShowS
$cshowList :: [CopyJob] -> ShowS
show :: CopyJob -> String
$cshow :: CopyJob -> String
showsPrec :: Int -> CopyJob -> ShowS
$cshowsPrec :: Int -> CopyJob -> ShowS
Prelude.Show, forall x. Rep CopyJob x -> CopyJob
forall x. CopyJob -> Rep CopyJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyJob x -> CopyJob
$cfrom :: forall x. CopyJob -> Rep CopyJob x
Prelude.Generic)

-- |
-- Create a value of 'CopyJob' 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', 'copyJob_accountId' - The account ID that owns the copy job.
--
-- 'backupSizeInBytes', 'copyJob_backupSizeInBytes' - The size, in bytes, of a copy job.
--
-- 'childJobsInState', 'copyJob_childJobsInState' - This returns the statistics of the included child (nested) copy jobs.
--
-- 'completionDate', 'copyJob_completionDate' - The date and time a copy 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.
--
-- 'compositeMemberIdentifier', 'copyJob_compositeMemberIdentifier' - This is the identifier of a resource within a composite group, such as
-- nested (child) recovery point belonging to a composite (parent) stack.
-- The ID is transferred from the
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/resources-section-structure.html#resources-section-structure-syntax logical ID>
-- within a stack.
--
-- 'copyJobId', 'copyJob_copyJobId' - Uniquely identifies a copy job.
--
-- 'createdBy', 'copyJob_createdBy' - Undocumented member.
--
-- 'creationDate', 'copyJob_creationDate' - The date and time a copy 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.
--
-- 'destinationBackupVaultArn', 'copyJob_destinationBackupVaultArn' - An Amazon Resource Name (ARN) that uniquely identifies a destination
-- copy vault; for example,
-- @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
--
-- 'destinationRecoveryPointArn', 'copyJob_destinationRecoveryPointArn' - An ARN that uniquely identifies a destination recovery point; for
-- example,
-- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
--
-- 'iamRoleArn', 'copyJob_iamRoleArn' - Specifies the IAM role ARN used to copy the target recovery point; for
-- example, @arn:aws:iam::123456789012:role\/S3Access@.
--
-- 'isParent', 'copyJob_isParent' - This is a boolean value indicating this is a parent (composite) copy
-- job.
--
-- 'numberOfChildJobs', 'copyJob_numberOfChildJobs' - This is the number of child (nested) copy jobs.
--
-- 'parentJobId', 'copyJob_parentJobId' - This uniquely identifies a request to Backup to copy a resource. The
-- return will be the parent (composite) job ID.
--
-- 'resourceArn', 'copyJob_resourceArn' - The Amazon Web Services resource to be copied; for example, an Amazon
-- Elastic Block Store (Amazon EBS) volume or an Amazon Relational Database
-- Service (Amazon RDS) database.
--
-- 'resourceType', 'copyJob_resourceType' - The type of Amazon Web Services resource to be copied; for example, an
-- Amazon Elastic Block Store (Amazon EBS) volume or an Amazon Relational
-- Database Service (Amazon RDS) database.
--
-- 'sourceBackupVaultArn', 'copyJob_sourceBackupVaultArn' - An Amazon Resource Name (ARN) that uniquely identifies a source copy
-- vault; for example,
-- @arn:aws:backup:us-east-1:123456789012:vault:aBackupVault@.
--
-- 'sourceRecoveryPointArn', 'copyJob_sourceRecoveryPointArn' - An ARN that uniquely identifies a source recovery point; for example,
-- @arn:aws:backup:us-east-1:123456789012:recovery-point:1EB3B5E7-9EB0-435A-A80B-108B488B0D45@.
--
-- 'state', 'copyJob_state' - The current state of a copy job.
--
-- 'statusMessage', 'copyJob_statusMessage' - A detailed message explaining the status of the job to copy a resource.
newCopyJob ::
  CopyJob
newCopyJob :: CopyJob
newCopyJob =
  CopyJob'
    { $sel:accountId:CopyJob' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:backupSizeInBytes:CopyJob' :: Maybe Integer
backupSizeInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:childJobsInState:CopyJob' :: Maybe (HashMap CopyJobState Integer)
childJobsInState = forall a. Maybe a
Prelude.Nothing,
      $sel:completionDate:CopyJob' :: Maybe POSIX
completionDate = forall a. Maybe a
Prelude.Nothing,
      $sel:compositeMemberIdentifier:CopyJob' :: Maybe Text
compositeMemberIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:copyJobId:CopyJob' :: Maybe Text
copyJobId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:CopyJob' :: Maybe RecoveryPointCreator
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:CopyJob' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationBackupVaultArn:CopyJob' :: Maybe Text
destinationBackupVaultArn = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationRecoveryPointArn:CopyJob' :: Maybe Text
destinationRecoveryPointArn = forall a. Maybe a
Prelude.Nothing,
      $sel:iamRoleArn:CopyJob' :: Maybe Text
iamRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:isParent:CopyJob' :: Maybe Bool
isParent = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfChildJobs:CopyJob' :: Maybe Integer
numberOfChildJobs = forall a. Maybe a
Prelude.Nothing,
      $sel:parentJobId:CopyJob' :: Maybe Text
parentJobId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:CopyJob' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:CopyJob' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceBackupVaultArn:CopyJob' :: Maybe Text
sourceBackupVaultArn = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceRecoveryPointArn:CopyJob' :: Maybe Text
sourceRecoveryPointArn = forall a. Maybe a
Prelude.Nothing,
      $sel:state:CopyJob' :: Maybe CopyJobState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:CopyJob' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The size, in bytes, of a copy job.
copyJob_backupSizeInBytes :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Integer)
copyJob_backupSizeInBytes :: Lens' CopyJob (Maybe Integer)
copyJob_backupSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Integer
backupSizeInBytes :: Maybe Integer
$sel:backupSizeInBytes:CopyJob' :: CopyJob -> Maybe Integer
backupSizeInBytes} -> Maybe Integer
backupSizeInBytes) (\s :: CopyJob
s@CopyJob' {} Maybe Integer
a -> CopyJob
s {$sel:backupSizeInBytes:CopyJob' :: Maybe Integer
backupSizeInBytes = Maybe Integer
a} :: CopyJob)

-- | This returns the statistics of the included child (nested) copy jobs.
copyJob_childJobsInState :: Lens.Lens' CopyJob (Prelude.Maybe (Prelude.HashMap CopyJobState Prelude.Integer))
copyJob_childJobsInState :: Lens' CopyJob (Maybe (HashMap CopyJobState Integer))
copyJob_childJobsInState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe (HashMap CopyJobState Integer)
childJobsInState :: Maybe (HashMap CopyJobState Integer)
$sel:childJobsInState:CopyJob' :: CopyJob -> Maybe (HashMap CopyJobState Integer)
childJobsInState} -> Maybe (HashMap CopyJobState Integer)
childJobsInState) (\s :: CopyJob
s@CopyJob' {} Maybe (HashMap CopyJobState Integer)
a -> CopyJob
s {$sel:childJobsInState:CopyJob' :: Maybe (HashMap CopyJobState Integer)
childJobsInState = Maybe (HashMap CopyJobState Integer)
a} :: CopyJob) 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 date and time a copy 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.
copyJob_completionDate :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.UTCTime)
copyJob_completionDate :: Lens' CopyJob (Maybe UTCTime)
copyJob_completionDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe POSIX
completionDate :: Maybe POSIX
$sel:completionDate:CopyJob' :: CopyJob -> Maybe POSIX
completionDate} -> Maybe POSIX
completionDate) (\s :: CopyJob
s@CopyJob' {} Maybe POSIX
a -> CopyJob
s {$sel:completionDate:CopyJob' :: Maybe POSIX
completionDate = Maybe POSIX
a} :: CopyJob) 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

-- | This is the identifier of a resource within a composite group, such as
-- nested (child) recovery point belonging to a composite (parent) stack.
-- The ID is transferred from the
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/resources-section-structure.html#resources-section-structure-syntax logical ID>
-- within a stack.
copyJob_compositeMemberIdentifier :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Text)
copyJob_compositeMemberIdentifier :: Lens' CopyJob (Maybe Text)
copyJob_compositeMemberIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Text
compositeMemberIdentifier :: Maybe Text
$sel:compositeMemberIdentifier:CopyJob' :: CopyJob -> Maybe Text
compositeMemberIdentifier} -> Maybe Text
compositeMemberIdentifier) (\s :: CopyJob
s@CopyJob' {} Maybe Text
a -> CopyJob
s {$sel:compositeMemberIdentifier:CopyJob' :: Maybe Text
compositeMemberIdentifier = Maybe Text
a} :: CopyJob)

-- | Uniquely identifies a copy job.
copyJob_copyJobId :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Text)
copyJob_copyJobId :: Lens' CopyJob (Maybe Text)
copyJob_copyJobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Text
copyJobId :: Maybe Text
$sel:copyJobId:CopyJob' :: CopyJob -> Maybe Text
copyJobId} -> Maybe Text
copyJobId) (\s :: CopyJob
s@CopyJob' {} Maybe Text
a -> CopyJob
s {$sel:copyJobId:CopyJob' :: Maybe Text
copyJobId = Maybe Text
a} :: CopyJob)

-- | Undocumented member.
copyJob_createdBy :: Lens.Lens' CopyJob (Prelude.Maybe RecoveryPointCreator)
copyJob_createdBy :: Lens' CopyJob (Maybe RecoveryPointCreator)
copyJob_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe RecoveryPointCreator
createdBy :: Maybe RecoveryPointCreator
$sel:createdBy:CopyJob' :: CopyJob -> Maybe RecoveryPointCreator
createdBy} -> Maybe RecoveryPointCreator
createdBy) (\s :: CopyJob
s@CopyJob' {} Maybe RecoveryPointCreator
a -> CopyJob
s {$sel:createdBy:CopyJob' :: Maybe RecoveryPointCreator
createdBy = Maybe RecoveryPointCreator
a} :: CopyJob)

-- | The date and time a copy 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.
copyJob_creationDate :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.UTCTime)
copyJob_creationDate :: Lens' CopyJob (Maybe UTCTime)
copyJob_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:CopyJob' :: CopyJob -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: CopyJob
s@CopyJob' {} Maybe POSIX
a -> CopyJob
s {$sel:creationDate:CopyJob' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: CopyJob) 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

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

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

-- | Specifies the IAM role ARN used to copy the target recovery point; for
-- example, @arn:aws:iam::123456789012:role\/S3Access@.
copyJob_iamRoleArn :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Text)
copyJob_iamRoleArn :: Lens' CopyJob (Maybe Text)
copyJob_iamRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Text
iamRoleArn :: Maybe Text
$sel:iamRoleArn:CopyJob' :: CopyJob -> Maybe Text
iamRoleArn} -> Maybe Text
iamRoleArn) (\s :: CopyJob
s@CopyJob' {} Maybe Text
a -> CopyJob
s {$sel:iamRoleArn:CopyJob' :: Maybe Text
iamRoleArn = Maybe Text
a} :: CopyJob)

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

-- | This is the number of child (nested) copy jobs.
copyJob_numberOfChildJobs :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Integer)
copyJob_numberOfChildJobs :: Lens' CopyJob (Maybe Integer)
copyJob_numberOfChildJobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Integer
numberOfChildJobs :: Maybe Integer
$sel:numberOfChildJobs:CopyJob' :: CopyJob -> Maybe Integer
numberOfChildJobs} -> Maybe Integer
numberOfChildJobs) (\s :: CopyJob
s@CopyJob' {} Maybe Integer
a -> CopyJob
s {$sel:numberOfChildJobs:CopyJob' :: Maybe Integer
numberOfChildJobs = Maybe Integer
a} :: CopyJob)

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

-- | The Amazon Web Services resource to be copied; for example, an Amazon
-- Elastic Block Store (Amazon EBS) volume or an Amazon Relational Database
-- Service (Amazon RDS) database.
copyJob_resourceArn :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Text)
copyJob_resourceArn :: Lens' CopyJob (Maybe Text)
copyJob_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:CopyJob' :: CopyJob -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: CopyJob
s@CopyJob' {} Maybe Text
a -> CopyJob
s {$sel:resourceArn:CopyJob' :: Maybe Text
resourceArn = Maybe Text
a} :: CopyJob)

-- | The type of Amazon Web Services resource to be copied; for example, an
-- Amazon Elastic Block Store (Amazon EBS) volume or an Amazon Relational
-- Database Service (Amazon RDS) database.
copyJob_resourceType :: Lens.Lens' CopyJob (Prelude.Maybe Prelude.Text)
copyJob_resourceType :: Lens' CopyJob (Maybe Text)
copyJob_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:CopyJob' :: CopyJob -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: CopyJob
s@CopyJob' {} Maybe Text
a -> CopyJob
s {$sel:resourceType:CopyJob' :: Maybe Text
resourceType = Maybe Text
a} :: CopyJob)

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

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

-- | The current state of a copy job.
copyJob_state :: Lens.Lens' CopyJob (Prelude.Maybe CopyJobState)
copyJob_state :: Lens' CopyJob (Maybe CopyJobState)
copyJob_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyJob' {Maybe CopyJobState
state :: Maybe CopyJobState
$sel:state:CopyJob' :: CopyJob -> Maybe CopyJobState
state} -> Maybe CopyJobState
state) (\s :: CopyJob
s@CopyJob' {} Maybe CopyJobState
a -> CopyJob
s {$sel:state:CopyJob' :: Maybe CopyJobState
state = Maybe CopyJobState
a} :: CopyJob)

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

instance Data.FromJSON CopyJob where
  parseJSON :: Value -> Parser CopyJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CopyJob"
      ( \Object
x ->
          Maybe Text
-> Maybe Integer
-> Maybe (HashMap CopyJobState Integer)
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe RecoveryPointCreator
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe CopyJobState
-> Maybe Text
-> CopyJob
CopyJob'
            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
"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
"ChildJobsInState"
                            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
"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
"CompositeMemberIdentifier")
            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
"CopyJobId")
            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
"DestinationBackupVaultArn")
            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
"DestinationRecoveryPointArn")
            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
"NumberOfChildJobs")
            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
"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
"SourceBackupVaultArn")
            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
"SourceRecoveryPointArn")
            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 CopyJob where
  hashWithSalt :: Int -> CopyJob -> Int
hashWithSalt Int
_salt CopyJob' {Maybe Bool
Maybe Integer
Maybe Text
Maybe (HashMap CopyJobState Integer)
Maybe POSIX
Maybe CopyJobState
Maybe RecoveryPointCreator
statusMessage :: Maybe Text
state :: Maybe CopyJobState
sourceRecoveryPointArn :: Maybe Text
sourceBackupVaultArn :: Maybe Text
resourceType :: Maybe Text
resourceArn :: Maybe Text
parentJobId :: Maybe Text
numberOfChildJobs :: Maybe Integer
isParent :: Maybe Bool
iamRoleArn :: Maybe Text
destinationRecoveryPointArn :: Maybe Text
destinationBackupVaultArn :: Maybe Text
creationDate :: Maybe POSIX
createdBy :: Maybe RecoveryPointCreator
copyJobId :: Maybe Text
compositeMemberIdentifier :: Maybe Text
completionDate :: Maybe POSIX
childJobsInState :: Maybe (HashMap CopyJobState Integer)
backupSizeInBytes :: Maybe Integer
accountId :: Maybe Text
$sel:statusMessage:CopyJob' :: CopyJob -> Maybe Text
$sel:state:CopyJob' :: CopyJob -> Maybe CopyJobState
$sel:sourceRecoveryPointArn:CopyJob' :: CopyJob -> Maybe Text
$sel:sourceBackupVaultArn:CopyJob' :: CopyJob -> Maybe Text
$sel:resourceType:CopyJob' :: CopyJob -> Maybe Text
$sel:resourceArn:CopyJob' :: CopyJob -> Maybe Text
$sel:parentJobId:CopyJob' :: CopyJob -> Maybe Text
$sel:numberOfChildJobs:CopyJob' :: CopyJob -> Maybe Integer
$sel:isParent:CopyJob' :: CopyJob -> Maybe Bool
$sel:iamRoleArn:CopyJob' :: CopyJob -> Maybe Text
$sel:destinationRecoveryPointArn:CopyJob' :: CopyJob -> Maybe Text
$sel:destinationBackupVaultArn:CopyJob' :: CopyJob -> Maybe Text
$sel:creationDate:CopyJob' :: CopyJob -> Maybe POSIX
$sel:createdBy:CopyJob' :: CopyJob -> Maybe RecoveryPointCreator
$sel:copyJobId:CopyJob' :: CopyJob -> Maybe Text
$sel:compositeMemberIdentifier:CopyJob' :: CopyJob -> Maybe Text
$sel:completionDate:CopyJob' :: CopyJob -> Maybe POSIX
$sel:childJobsInState:CopyJob' :: CopyJob -> Maybe (HashMap CopyJobState Integer)
$sel:backupSizeInBytes:CopyJob' :: CopyJob -> Maybe Integer
$sel:accountId:CopyJob' :: CopyJob -> 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 Integer
backupSizeInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap CopyJobState Integer)
childJobsInState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
completionDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
compositeMemberIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
copyJobId
      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 Text
destinationBackupVaultArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationRecoveryPointArn
      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 Integer
numberOfChildJobs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parentJobId
      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 Text
sourceBackupVaultArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceRecoveryPointArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CopyJobState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusMessage

instance Prelude.NFData CopyJob where
  rnf :: CopyJob -> ()
rnf CopyJob' {Maybe Bool
Maybe Integer
Maybe Text
Maybe (HashMap CopyJobState Integer)
Maybe POSIX
Maybe CopyJobState
Maybe RecoveryPointCreator
statusMessage :: Maybe Text
state :: Maybe CopyJobState
sourceRecoveryPointArn :: Maybe Text
sourceBackupVaultArn :: Maybe Text
resourceType :: Maybe Text
resourceArn :: Maybe Text
parentJobId :: Maybe Text
numberOfChildJobs :: Maybe Integer
isParent :: Maybe Bool
iamRoleArn :: Maybe Text
destinationRecoveryPointArn :: Maybe Text
destinationBackupVaultArn :: Maybe Text
creationDate :: Maybe POSIX
createdBy :: Maybe RecoveryPointCreator
copyJobId :: Maybe Text
compositeMemberIdentifier :: Maybe Text
completionDate :: Maybe POSIX
childJobsInState :: Maybe (HashMap CopyJobState Integer)
backupSizeInBytes :: Maybe Integer
accountId :: Maybe Text
$sel:statusMessage:CopyJob' :: CopyJob -> Maybe Text
$sel:state:CopyJob' :: CopyJob -> Maybe CopyJobState
$sel:sourceRecoveryPointArn:CopyJob' :: CopyJob -> Maybe Text
$sel:sourceBackupVaultArn:CopyJob' :: CopyJob -> Maybe Text
$sel:resourceType:CopyJob' :: CopyJob -> Maybe Text
$sel:resourceArn:CopyJob' :: CopyJob -> Maybe Text
$sel:parentJobId:CopyJob' :: CopyJob -> Maybe Text
$sel:numberOfChildJobs:CopyJob' :: CopyJob -> Maybe Integer
$sel:isParent:CopyJob' :: CopyJob -> Maybe Bool
$sel:iamRoleArn:CopyJob' :: CopyJob -> Maybe Text
$sel:destinationRecoveryPointArn:CopyJob' :: CopyJob -> Maybe Text
$sel:destinationBackupVaultArn:CopyJob' :: CopyJob -> Maybe Text
$sel:creationDate:CopyJob' :: CopyJob -> Maybe POSIX
$sel:createdBy:CopyJob' :: CopyJob -> Maybe RecoveryPointCreator
$sel:copyJobId:CopyJob' :: CopyJob -> Maybe Text
$sel:compositeMemberIdentifier:CopyJob' :: CopyJob -> Maybe Text
$sel:completionDate:CopyJob' :: CopyJob -> Maybe POSIX
$sel:childJobsInState:CopyJob' :: CopyJob -> Maybe (HashMap CopyJobState Integer)
$sel:backupSizeInBytes:CopyJob' :: CopyJob -> Maybe Integer
$sel:accountId:CopyJob' :: CopyJob -> 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 Integer
backupSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap CopyJobState Integer)
childJobsInState
      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 Text
compositeMemberIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copyJobId
      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 Text
destinationBackupVaultArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationRecoveryPointArn
      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 Integer
numberOfChildJobs
      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
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 Text
sourceBackupVaultArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceRecoveryPointArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CopyJobState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusMessage