{-# 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.Snowball.Types.JobMetadata
-- 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.Snowball.Types.JobMetadata where

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
import Amazonka.Snowball.Types.DataTransfer
import Amazonka.Snowball.Types.DeviceConfiguration
import Amazonka.Snowball.Types.JobLogs
import Amazonka.Snowball.Types.JobResource
import Amazonka.Snowball.Types.JobState
import Amazonka.Snowball.Types.JobType
import Amazonka.Snowball.Types.Notification
import Amazonka.Snowball.Types.OnDeviceServiceConfiguration
import Amazonka.Snowball.Types.RemoteManagement
import Amazonka.Snowball.Types.ShippingDetails
import Amazonka.Snowball.Types.SnowballCapacity
import Amazonka.Snowball.Types.SnowballType
import Amazonka.Snowball.Types.TaxDocuments

-- | Contains information about a specific job including shipping
-- information, job status, and other important metadata. This information
-- is returned as a part of the response syntax of the @DescribeJob@
-- action.
--
-- /See:/ 'newJobMetadata' smart constructor.
data JobMetadata = JobMetadata'
  { -- | The ID for the address that you want the Snow device shipped to.
    JobMetadata -> Maybe Text
addressId :: Prelude.Maybe Prelude.Text,
    -- | The 39-character ID for the cluster, for example
    -- @CID123e4567-e89b-12d3-a456-426655440000@.
    JobMetadata -> Maybe Text
clusterId :: Prelude.Maybe Prelude.Text,
    -- | The creation date for this job.
    JobMetadata -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | A value that defines the real-time status of a Snow device\'s data
    -- transfer while the device is at Amazon Web Services. This data is only
    -- available while a job has a @JobState@ value of @InProgress@, for both
    -- import and export jobs.
    JobMetadata -> Maybe DataTransfer
dataTransferProgress :: Prelude.Maybe DataTransfer,
    -- | The description of the job, provided at job creation.
    JobMetadata -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    JobMetadata -> Maybe DeviceConfiguration
deviceConfiguration :: Prelude.Maybe DeviceConfiguration,
    -- | The ID of the address that you want a job shipped to, after it will be
    -- shipped to its primary address. This field is not supported in most
    -- regions.
    JobMetadata -> Maybe Text
forwardingAddressId :: Prelude.Maybe Prelude.Text,
    -- | The automatically generated ID for a job, for example
    -- @JID123e4567-e89b-12d3-a456-426655440000@.
    JobMetadata -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | Links to Amazon S3 presigned URLs for the job report and logs. For
    -- import jobs, the PDF job report becomes available at the end of the
    -- import process. For export jobs, your job report typically becomes
    -- available while the Snow device for your job part is being delivered to
    -- you.
    JobMetadata -> Maybe JobLogs
jobLogInfo :: Prelude.Maybe JobLogs,
    -- | The current status of the jobs.
    JobMetadata -> Maybe JobState
jobState :: Prelude.Maybe JobState,
    -- | The type of job.
    JobMetadata -> Maybe JobType
jobType :: Prelude.Maybe JobType,
    -- | The Amazon Resource Name (ARN) for the Key Management Service (KMS) key
    -- associated with this job. This ARN was created using the
    -- <https://docs.aws.amazon.com/kms/latest/APIReference/API_CreateKey.html CreateKey>
    -- API action in KMS.
    JobMetadata -> Maybe Text
kmsKeyARN :: Prelude.Maybe Prelude.Text,
    -- | The ID of the long-term pricing type for the device.
    JobMetadata -> Maybe Text
longTermPricingId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Simple Notification Service (Amazon SNS) notification
    -- settings associated with a specific job. The @Notification@ object is
    -- returned as a part of the response syntax of the @DescribeJob@ action in
    -- the @JobMetadata@ data type.
    JobMetadata -> Maybe Notification
notification :: Prelude.Maybe Notification,
    -- | Represents metadata and configuration settings for services on an Amazon
    -- Web Services Snow Family device.
    JobMetadata -> Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration :: Prelude.Maybe OnDeviceServiceConfiguration,
    -- | Allows you to securely operate and manage Snowcone devices remotely from
    -- outside of your internal network. When set to @INSTALLED_AUTOSTART@,
    -- remote management will automatically be available when the device
    -- arrives at your location. Otherwise, you need to use the Snowball Client
    -- to manage the device.
    JobMetadata -> Maybe RemoteManagement
remoteManagement :: Prelude.Maybe RemoteManagement,
    -- | An array of @S3Resource@ objects. Each @S3Resource@ object represents an
    -- Amazon S3 bucket that your transferred data will be exported from or
    -- imported into.
    JobMetadata -> Maybe JobResource
resources :: Prelude.Maybe JobResource,
    -- | The role ARN associated with this job. This ARN was created using the
    -- <https://docs.aws.amazon.com/IAM/latest/APIReference/API_CreateRole.html CreateRole>
    -- API action in Identity and Access Management.
    JobMetadata -> Maybe Text
roleARN :: Prelude.Maybe Prelude.Text,
    -- | A job\'s shipping information, including inbound and outbound tracking
    -- numbers and shipping speed options.
    JobMetadata -> Maybe ShippingDetails
shippingDetails :: Prelude.Maybe ShippingDetails,
    -- | The Snow device capacity preference for this job, specified at job
    -- creation. In US regions, you can choose between 50 TB and 80 TB
    -- Snowballs. All other regions use 80 TB capacity Snowballs.
    --
    -- For more information, see
    -- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/snowcone-guide\/snow-device-types.html\"
    -- (Snow Family Devices and Capacity) in the /Snowcone User Guide/ or
    -- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/developer-guide\/snow-device-types.html\"
    -- (Snow Family Devices and Capacity) in the /Snowcone User Guide/.
    JobMetadata -> Maybe SnowballCapacity
snowballCapacityPreference :: Prelude.Maybe SnowballCapacity,
    -- | The type of device used with this job.
    JobMetadata -> Maybe SnowballType
snowballType :: Prelude.Maybe SnowballType,
    -- | The metadata associated with the tax documents required in your Amazon
    -- Web Services Region.
    JobMetadata -> Maybe TaxDocuments
taxDocuments :: Prelude.Maybe TaxDocuments
  }
  deriving (JobMetadata -> JobMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobMetadata -> JobMetadata -> Bool
$c/= :: JobMetadata -> JobMetadata -> Bool
== :: JobMetadata -> JobMetadata -> Bool
$c== :: JobMetadata -> JobMetadata -> Bool
Prelude.Eq, ReadPrec [JobMetadata]
ReadPrec JobMetadata
Int -> ReadS JobMetadata
ReadS [JobMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobMetadata]
$creadListPrec :: ReadPrec [JobMetadata]
readPrec :: ReadPrec JobMetadata
$creadPrec :: ReadPrec JobMetadata
readList :: ReadS [JobMetadata]
$creadList :: ReadS [JobMetadata]
readsPrec :: Int -> ReadS JobMetadata
$creadsPrec :: Int -> ReadS JobMetadata
Prelude.Read, Int -> JobMetadata -> ShowS
[JobMetadata] -> ShowS
JobMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobMetadata] -> ShowS
$cshowList :: [JobMetadata] -> ShowS
show :: JobMetadata -> String
$cshow :: JobMetadata -> String
showsPrec :: Int -> JobMetadata -> ShowS
$cshowsPrec :: Int -> JobMetadata -> ShowS
Prelude.Show, forall x. Rep JobMetadata x -> JobMetadata
forall x. JobMetadata -> Rep JobMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobMetadata x -> JobMetadata
$cfrom :: forall x. JobMetadata -> Rep JobMetadata x
Prelude.Generic)

-- |
-- Create a value of 'JobMetadata' 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:
--
-- 'addressId', 'jobMetadata_addressId' - The ID for the address that you want the Snow device shipped to.
--
-- 'clusterId', 'jobMetadata_clusterId' - The 39-character ID for the cluster, for example
-- @CID123e4567-e89b-12d3-a456-426655440000@.
--
-- 'creationDate', 'jobMetadata_creationDate' - The creation date for this job.
--
-- 'dataTransferProgress', 'jobMetadata_dataTransferProgress' - A value that defines the real-time status of a Snow device\'s data
-- transfer while the device is at Amazon Web Services. This data is only
-- available while a job has a @JobState@ value of @InProgress@, for both
-- import and export jobs.
--
-- 'description', 'jobMetadata_description' - The description of the job, provided at job creation.
--
-- 'deviceConfiguration', 'jobMetadata_deviceConfiguration' - Undocumented member.
--
-- 'forwardingAddressId', 'jobMetadata_forwardingAddressId' - The ID of the address that you want a job shipped to, after it will be
-- shipped to its primary address. This field is not supported in most
-- regions.
--
-- 'jobId', 'jobMetadata_jobId' - The automatically generated ID for a job, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
--
-- 'jobLogInfo', 'jobMetadata_jobLogInfo' - Links to Amazon S3 presigned URLs for the job report and logs. For
-- import jobs, the PDF job report becomes available at the end of the
-- import process. For export jobs, your job report typically becomes
-- available while the Snow device for your job part is being delivered to
-- you.
--
-- 'jobState', 'jobMetadata_jobState' - The current status of the jobs.
--
-- 'jobType', 'jobMetadata_jobType' - The type of job.
--
-- 'kmsKeyARN', 'jobMetadata_kmsKeyARN' - The Amazon Resource Name (ARN) for the Key Management Service (KMS) key
-- associated with this job. This ARN was created using the
-- <https://docs.aws.amazon.com/kms/latest/APIReference/API_CreateKey.html CreateKey>
-- API action in KMS.
--
-- 'longTermPricingId', 'jobMetadata_longTermPricingId' - The ID of the long-term pricing type for the device.
--
-- 'notification', 'jobMetadata_notification' - The Amazon Simple Notification Service (Amazon SNS) notification
-- settings associated with a specific job. The @Notification@ object is
-- returned as a part of the response syntax of the @DescribeJob@ action in
-- the @JobMetadata@ data type.
--
-- 'onDeviceServiceConfiguration', 'jobMetadata_onDeviceServiceConfiguration' - Represents metadata and configuration settings for services on an Amazon
-- Web Services Snow Family device.
--
-- 'remoteManagement', 'jobMetadata_remoteManagement' - Allows you to securely operate and manage Snowcone devices remotely from
-- outside of your internal network. When set to @INSTALLED_AUTOSTART@,
-- remote management will automatically be available when the device
-- arrives at your location. Otherwise, you need to use the Snowball Client
-- to manage the device.
--
-- 'resources', 'jobMetadata_resources' - An array of @S3Resource@ objects. Each @S3Resource@ object represents an
-- Amazon S3 bucket that your transferred data will be exported from or
-- imported into.
--
-- 'roleARN', 'jobMetadata_roleARN' - The role ARN associated with this job. This ARN was created using the
-- <https://docs.aws.amazon.com/IAM/latest/APIReference/API_CreateRole.html CreateRole>
-- API action in Identity and Access Management.
--
-- 'shippingDetails', 'jobMetadata_shippingDetails' - A job\'s shipping information, including inbound and outbound tracking
-- numbers and shipping speed options.
--
-- 'snowballCapacityPreference', 'jobMetadata_snowballCapacityPreference' - The Snow device capacity preference for this job, specified at job
-- creation. In US regions, you can choose between 50 TB and 80 TB
-- Snowballs. All other regions use 80 TB capacity Snowballs.
--
-- For more information, see
-- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/snowcone-guide\/snow-device-types.html\"
-- (Snow Family Devices and Capacity) in the /Snowcone User Guide/ or
-- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/developer-guide\/snow-device-types.html\"
-- (Snow Family Devices and Capacity) in the /Snowcone User Guide/.
--
-- 'snowballType', 'jobMetadata_snowballType' - The type of device used with this job.
--
-- 'taxDocuments', 'jobMetadata_taxDocuments' - The metadata associated with the tax documents required in your Amazon
-- Web Services Region.
newJobMetadata ::
  JobMetadata
newJobMetadata :: JobMetadata
newJobMetadata =
  JobMetadata'
    { $sel:addressId:JobMetadata' :: Maybe Text
addressId = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterId:JobMetadata' :: Maybe Text
clusterId = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:JobMetadata' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:dataTransferProgress:JobMetadata' :: Maybe DataTransfer
dataTransferProgress = forall a. Maybe a
Prelude.Nothing,
      $sel:description:JobMetadata' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceConfiguration:JobMetadata' :: Maybe DeviceConfiguration
deviceConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:forwardingAddressId:JobMetadata' :: Maybe Text
forwardingAddressId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:JobMetadata' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobLogInfo:JobMetadata' :: Maybe JobLogs
jobLogInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:jobState:JobMetadata' :: Maybe JobState
jobState = forall a. Maybe a
Prelude.Nothing,
      $sel:jobType:JobMetadata' :: Maybe JobType
jobType = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyARN:JobMetadata' :: Maybe Text
kmsKeyARN = forall a. Maybe a
Prelude.Nothing,
      $sel:longTermPricingId:JobMetadata' :: Maybe Text
longTermPricingId = forall a. Maybe a
Prelude.Nothing,
      $sel:notification:JobMetadata' :: Maybe Notification
notification = forall a. Maybe a
Prelude.Nothing,
      $sel:onDeviceServiceConfiguration:JobMetadata' :: Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:remoteManagement:JobMetadata' :: Maybe RemoteManagement
remoteManagement = forall a. Maybe a
Prelude.Nothing,
      $sel:resources:JobMetadata' :: Maybe JobResource
resources = forall a. Maybe a
Prelude.Nothing,
      $sel:roleARN:JobMetadata' :: Maybe Text
roleARN = forall a. Maybe a
Prelude.Nothing,
      $sel:shippingDetails:JobMetadata' :: Maybe ShippingDetails
shippingDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:snowballCapacityPreference:JobMetadata' :: Maybe SnowballCapacity
snowballCapacityPreference = forall a. Maybe a
Prelude.Nothing,
      $sel:snowballType:JobMetadata' :: Maybe SnowballType
snowballType = forall a. Maybe a
Prelude.Nothing,
      $sel:taxDocuments:JobMetadata' :: Maybe TaxDocuments
taxDocuments = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID for the address that you want the Snow device shipped to.
jobMetadata_addressId :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_addressId :: Lens' JobMetadata (Maybe Text)
jobMetadata_addressId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
addressId :: Maybe Text
$sel:addressId:JobMetadata' :: JobMetadata -> Maybe Text
addressId} -> Maybe Text
addressId) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:addressId:JobMetadata' :: Maybe Text
addressId = Maybe Text
a} :: JobMetadata)

-- | The 39-character ID for the cluster, for example
-- @CID123e4567-e89b-12d3-a456-426655440000@.
jobMetadata_clusterId :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_clusterId :: Lens' JobMetadata (Maybe Text)
jobMetadata_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
clusterId :: Maybe Text
$sel:clusterId:JobMetadata' :: JobMetadata -> Maybe Text
clusterId} -> Maybe Text
clusterId) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:clusterId:JobMetadata' :: Maybe Text
clusterId = Maybe Text
a} :: JobMetadata)

-- | The creation date for this job.
jobMetadata_creationDate :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.UTCTime)
jobMetadata_creationDate :: Lens' JobMetadata (Maybe UTCTime)
jobMetadata_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:JobMetadata' :: JobMetadata -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: JobMetadata
s@JobMetadata' {} Maybe POSIX
a -> JobMetadata
s {$sel:creationDate:JobMetadata' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: JobMetadata) 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

-- | A value that defines the real-time status of a Snow device\'s data
-- transfer while the device is at Amazon Web Services. This data is only
-- available while a job has a @JobState@ value of @InProgress@, for both
-- import and export jobs.
jobMetadata_dataTransferProgress :: Lens.Lens' JobMetadata (Prelude.Maybe DataTransfer)
jobMetadata_dataTransferProgress :: Lens' JobMetadata (Maybe DataTransfer)
jobMetadata_dataTransferProgress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe DataTransfer
dataTransferProgress :: Maybe DataTransfer
$sel:dataTransferProgress:JobMetadata' :: JobMetadata -> Maybe DataTransfer
dataTransferProgress} -> Maybe DataTransfer
dataTransferProgress) (\s :: JobMetadata
s@JobMetadata' {} Maybe DataTransfer
a -> JobMetadata
s {$sel:dataTransferProgress:JobMetadata' :: Maybe DataTransfer
dataTransferProgress = Maybe DataTransfer
a} :: JobMetadata)

-- | The description of the job, provided at job creation.
jobMetadata_description :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_description :: Lens' JobMetadata (Maybe Text)
jobMetadata_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
description :: Maybe Text
$sel:description:JobMetadata' :: JobMetadata -> Maybe Text
description} -> Maybe Text
description) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:description:JobMetadata' :: Maybe Text
description = Maybe Text
a} :: JobMetadata)

-- | Undocumented member.
jobMetadata_deviceConfiguration :: Lens.Lens' JobMetadata (Prelude.Maybe DeviceConfiguration)
jobMetadata_deviceConfiguration :: Lens' JobMetadata (Maybe DeviceConfiguration)
jobMetadata_deviceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe DeviceConfiguration
deviceConfiguration :: Maybe DeviceConfiguration
$sel:deviceConfiguration:JobMetadata' :: JobMetadata -> Maybe DeviceConfiguration
deviceConfiguration} -> Maybe DeviceConfiguration
deviceConfiguration) (\s :: JobMetadata
s@JobMetadata' {} Maybe DeviceConfiguration
a -> JobMetadata
s {$sel:deviceConfiguration:JobMetadata' :: Maybe DeviceConfiguration
deviceConfiguration = Maybe DeviceConfiguration
a} :: JobMetadata)

-- | The ID of the address that you want a job shipped to, after it will be
-- shipped to its primary address. This field is not supported in most
-- regions.
jobMetadata_forwardingAddressId :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_forwardingAddressId :: Lens' JobMetadata (Maybe Text)
jobMetadata_forwardingAddressId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
forwardingAddressId :: Maybe Text
$sel:forwardingAddressId:JobMetadata' :: JobMetadata -> Maybe Text
forwardingAddressId} -> Maybe Text
forwardingAddressId) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:forwardingAddressId:JobMetadata' :: Maybe Text
forwardingAddressId = Maybe Text
a} :: JobMetadata)

-- | The automatically generated ID for a job, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
jobMetadata_jobId :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_jobId :: Lens' JobMetadata (Maybe Text)
jobMetadata_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
jobId :: Maybe Text
$sel:jobId:JobMetadata' :: JobMetadata -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:jobId:JobMetadata' :: Maybe Text
jobId = Maybe Text
a} :: JobMetadata)

-- | Links to Amazon S3 presigned URLs for the job report and logs. For
-- import jobs, the PDF job report becomes available at the end of the
-- import process. For export jobs, your job report typically becomes
-- available while the Snow device for your job part is being delivered to
-- you.
jobMetadata_jobLogInfo :: Lens.Lens' JobMetadata (Prelude.Maybe JobLogs)
jobMetadata_jobLogInfo :: Lens' JobMetadata (Maybe JobLogs)
jobMetadata_jobLogInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe JobLogs
jobLogInfo :: Maybe JobLogs
$sel:jobLogInfo:JobMetadata' :: JobMetadata -> Maybe JobLogs
jobLogInfo} -> Maybe JobLogs
jobLogInfo) (\s :: JobMetadata
s@JobMetadata' {} Maybe JobLogs
a -> JobMetadata
s {$sel:jobLogInfo:JobMetadata' :: Maybe JobLogs
jobLogInfo = Maybe JobLogs
a} :: JobMetadata)

-- | The current status of the jobs.
jobMetadata_jobState :: Lens.Lens' JobMetadata (Prelude.Maybe JobState)
jobMetadata_jobState :: Lens' JobMetadata (Maybe JobState)
jobMetadata_jobState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe JobState
jobState :: Maybe JobState
$sel:jobState:JobMetadata' :: JobMetadata -> Maybe JobState
jobState} -> Maybe JobState
jobState) (\s :: JobMetadata
s@JobMetadata' {} Maybe JobState
a -> JobMetadata
s {$sel:jobState:JobMetadata' :: Maybe JobState
jobState = Maybe JobState
a} :: JobMetadata)

-- | The type of job.
jobMetadata_jobType :: Lens.Lens' JobMetadata (Prelude.Maybe JobType)
jobMetadata_jobType :: Lens' JobMetadata (Maybe JobType)
jobMetadata_jobType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe JobType
jobType :: Maybe JobType
$sel:jobType:JobMetadata' :: JobMetadata -> Maybe JobType
jobType} -> Maybe JobType
jobType) (\s :: JobMetadata
s@JobMetadata' {} Maybe JobType
a -> JobMetadata
s {$sel:jobType:JobMetadata' :: Maybe JobType
jobType = Maybe JobType
a} :: JobMetadata)

-- | The Amazon Resource Name (ARN) for the Key Management Service (KMS) key
-- associated with this job. This ARN was created using the
-- <https://docs.aws.amazon.com/kms/latest/APIReference/API_CreateKey.html CreateKey>
-- API action in KMS.
jobMetadata_kmsKeyARN :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_kmsKeyARN :: Lens' JobMetadata (Maybe Text)
jobMetadata_kmsKeyARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
kmsKeyARN :: Maybe Text
$sel:kmsKeyARN:JobMetadata' :: JobMetadata -> Maybe Text
kmsKeyARN} -> Maybe Text
kmsKeyARN) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:kmsKeyARN:JobMetadata' :: Maybe Text
kmsKeyARN = Maybe Text
a} :: JobMetadata)

-- | The ID of the long-term pricing type for the device.
jobMetadata_longTermPricingId :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_longTermPricingId :: Lens' JobMetadata (Maybe Text)
jobMetadata_longTermPricingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
longTermPricingId :: Maybe Text
$sel:longTermPricingId:JobMetadata' :: JobMetadata -> Maybe Text
longTermPricingId} -> Maybe Text
longTermPricingId) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:longTermPricingId:JobMetadata' :: Maybe Text
longTermPricingId = Maybe Text
a} :: JobMetadata)

-- | The Amazon Simple Notification Service (Amazon SNS) notification
-- settings associated with a specific job. The @Notification@ object is
-- returned as a part of the response syntax of the @DescribeJob@ action in
-- the @JobMetadata@ data type.
jobMetadata_notification :: Lens.Lens' JobMetadata (Prelude.Maybe Notification)
jobMetadata_notification :: Lens' JobMetadata (Maybe Notification)
jobMetadata_notification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Notification
notification :: Maybe Notification
$sel:notification:JobMetadata' :: JobMetadata -> Maybe Notification
notification} -> Maybe Notification
notification) (\s :: JobMetadata
s@JobMetadata' {} Maybe Notification
a -> JobMetadata
s {$sel:notification:JobMetadata' :: Maybe Notification
notification = Maybe Notification
a} :: JobMetadata)

-- | Represents metadata and configuration settings for services on an Amazon
-- Web Services Snow Family device.
jobMetadata_onDeviceServiceConfiguration :: Lens.Lens' JobMetadata (Prelude.Maybe OnDeviceServiceConfiguration)
jobMetadata_onDeviceServiceConfiguration :: Lens' JobMetadata (Maybe OnDeviceServiceConfiguration)
jobMetadata_onDeviceServiceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration :: Maybe OnDeviceServiceConfiguration
$sel:onDeviceServiceConfiguration:JobMetadata' :: JobMetadata -> Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration} -> Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration) (\s :: JobMetadata
s@JobMetadata' {} Maybe OnDeviceServiceConfiguration
a -> JobMetadata
s {$sel:onDeviceServiceConfiguration:JobMetadata' :: Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration = Maybe OnDeviceServiceConfiguration
a} :: JobMetadata)

-- | Allows you to securely operate and manage Snowcone devices remotely from
-- outside of your internal network. When set to @INSTALLED_AUTOSTART@,
-- remote management will automatically be available when the device
-- arrives at your location. Otherwise, you need to use the Snowball Client
-- to manage the device.
jobMetadata_remoteManagement :: Lens.Lens' JobMetadata (Prelude.Maybe RemoteManagement)
jobMetadata_remoteManagement :: Lens' JobMetadata (Maybe RemoteManagement)
jobMetadata_remoteManagement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe RemoteManagement
remoteManagement :: Maybe RemoteManagement
$sel:remoteManagement:JobMetadata' :: JobMetadata -> Maybe RemoteManagement
remoteManagement} -> Maybe RemoteManagement
remoteManagement) (\s :: JobMetadata
s@JobMetadata' {} Maybe RemoteManagement
a -> JobMetadata
s {$sel:remoteManagement:JobMetadata' :: Maybe RemoteManagement
remoteManagement = Maybe RemoteManagement
a} :: JobMetadata)

-- | An array of @S3Resource@ objects. Each @S3Resource@ object represents an
-- Amazon S3 bucket that your transferred data will be exported from or
-- imported into.
jobMetadata_resources :: Lens.Lens' JobMetadata (Prelude.Maybe JobResource)
jobMetadata_resources :: Lens' JobMetadata (Maybe JobResource)
jobMetadata_resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe JobResource
resources :: Maybe JobResource
$sel:resources:JobMetadata' :: JobMetadata -> Maybe JobResource
resources} -> Maybe JobResource
resources) (\s :: JobMetadata
s@JobMetadata' {} Maybe JobResource
a -> JobMetadata
s {$sel:resources:JobMetadata' :: Maybe JobResource
resources = Maybe JobResource
a} :: JobMetadata)

-- | The role ARN associated with this job. This ARN was created using the
-- <https://docs.aws.amazon.com/IAM/latest/APIReference/API_CreateRole.html CreateRole>
-- API action in Identity and Access Management.
jobMetadata_roleARN :: Lens.Lens' JobMetadata (Prelude.Maybe Prelude.Text)
jobMetadata_roleARN :: Lens' JobMetadata (Maybe Text)
jobMetadata_roleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe Text
roleARN :: Maybe Text
$sel:roleARN:JobMetadata' :: JobMetadata -> Maybe Text
roleARN} -> Maybe Text
roleARN) (\s :: JobMetadata
s@JobMetadata' {} Maybe Text
a -> JobMetadata
s {$sel:roleARN:JobMetadata' :: Maybe Text
roleARN = Maybe Text
a} :: JobMetadata)

-- | A job\'s shipping information, including inbound and outbound tracking
-- numbers and shipping speed options.
jobMetadata_shippingDetails :: Lens.Lens' JobMetadata (Prelude.Maybe ShippingDetails)
jobMetadata_shippingDetails :: Lens' JobMetadata (Maybe ShippingDetails)
jobMetadata_shippingDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe ShippingDetails
shippingDetails :: Maybe ShippingDetails
$sel:shippingDetails:JobMetadata' :: JobMetadata -> Maybe ShippingDetails
shippingDetails} -> Maybe ShippingDetails
shippingDetails) (\s :: JobMetadata
s@JobMetadata' {} Maybe ShippingDetails
a -> JobMetadata
s {$sel:shippingDetails:JobMetadata' :: Maybe ShippingDetails
shippingDetails = Maybe ShippingDetails
a} :: JobMetadata)

-- | The Snow device capacity preference for this job, specified at job
-- creation. In US regions, you can choose between 50 TB and 80 TB
-- Snowballs. All other regions use 80 TB capacity Snowballs.
--
-- For more information, see
-- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/snowcone-guide\/snow-device-types.html\"
-- (Snow Family Devices and Capacity) in the /Snowcone User Guide/ or
-- \"https:\/\/docs.aws.amazon.com\/snowball\/latest\/developer-guide\/snow-device-types.html\"
-- (Snow Family Devices and Capacity) in the /Snowcone User Guide/.
jobMetadata_snowballCapacityPreference :: Lens.Lens' JobMetadata (Prelude.Maybe SnowballCapacity)
jobMetadata_snowballCapacityPreference :: Lens' JobMetadata (Maybe SnowballCapacity)
jobMetadata_snowballCapacityPreference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe SnowballCapacity
snowballCapacityPreference :: Maybe SnowballCapacity
$sel:snowballCapacityPreference:JobMetadata' :: JobMetadata -> Maybe SnowballCapacity
snowballCapacityPreference} -> Maybe SnowballCapacity
snowballCapacityPreference) (\s :: JobMetadata
s@JobMetadata' {} Maybe SnowballCapacity
a -> JobMetadata
s {$sel:snowballCapacityPreference:JobMetadata' :: Maybe SnowballCapacity
snowballCapacityPreference = Maybe SnowballCapacity
a} :: JobMetadata)

-- | The type of device used with this job.
jobMetadata_snowballType :: Lens.Lens' JobMetadata (Prelude.Maybe SnowballType)
jobMetadata_snowballType :: Lens' JobMetadata (Maybe SnowballType)
jobMetadata_snowballType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe SnowballType
snowballType :: Maybe SnowballType
$sel:snowballType:JobMetadata' :: JobMetadata -> Maybe SnowballType
snowballType} -> Maybe SnowballType
snowballType) (\s :: JobMetadata
s@JobMetadata' {} Maybe SnowballType
a -> JobMetadata
s {$sel:snowballType:JobMetadata' :: Maybe SnowballType
snowballType = Maybe SnowballType
a} :: JobMetadata)

-- | The metadata associated with the tax documents required in your Amazon
-- Web Services Region.
jobMetadata_taxDocuments :: Lens.Lens' JobMetadata (Prelude.Maybe TaxDocuments)
jobMetadata_taxDocuments :: Lens' JobMetadata (Maybe TaxDocuments)
jobMetadata_taxDocuments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobMetadata' {Maybe TaxDocuments
taxDocuments :: Maybe TaxDocuments
$sel:taxDocuments:JobMetadata' :: JobMetadata -> Maybe TaxDocuments
taxDocuments} -> Maybe TaxDocuments
taxDocuments) (\s :: JobMetadata
s@JobMetadata' {} Maybe TaxDocuments
a -> JobMetadata
s {$sel:taxDocuments:JobMetadata' :: Maybe TaxDocuments
taxDocuments = Maybe TaxDocuments
a} :: JobMetadata)

instance Data.FromJSON JobMetadata where
  parseJSON :: Value -> Parser JobMetadata
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobMetadata"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe DataTransfer
-> Maybe Text
-> Maybe DeviceConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe JobLogs
-> Maybe JobState
-> Maybe JobType
-> Maybe Text
-> Maybe Text
-> Maybe Notification
-> Maybe OnDeviceServiceConfiguration
-> Maybe RemoteManagement
-> Maybe JobResource
-> Maybe Text
-> Maybe ShippingDetails
-> Maybe SnowballCapacity
-> Maybe SnowballType
-> Maybe TaxDocuments
-> JobMetadata
JobMetadata'
            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
"AddressId")
            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
"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
"DataTransferProgress")
            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
"Description")
            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
"DeviceConfiguration")
            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
"ForwardingAddressId")
            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
"JobId")
            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
"JobLogInfo")
            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
"JobState")
            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
"JobType")
            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
"KmsKeyARN")
            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
"LongTermPricingId")
            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
"Notification")
            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
"OnDeviceServiceConfiguration")
            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
"RemoteManagement")
            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
"Resources")
            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
"RoleARN")
            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
"ShippingDetails")
            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
"SnowballCapacityPreference")
            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
"SnowballType")
            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
"TaxDocuments")
      )

instance Prelude.Hashable JobMetadata where
  hashWithSalt :: Int -> JobMetadata -> Int
hashWithSalt Int
_salt JobMetadata' {Maybe Text
Maybe POSIX
Maybe DataTransfer
Maybe JobLogs
Maybe JobState
Maybe JobType
Maybe Notification
Maybe RemoteManagement
Maybe ShippingDetails
Maybe SnowballCapacity
Maybe SnowballType
Maybe OnDeviceServiceConfiguration
Maybe TaxDocuments
Maybe JobResource
Maybe DeviceConfiguration
taxDocuments :: Maybe TaxDocuments
snowballType :: Maybe SnowballType
snowballCapacityPreference :: Maybe SnowballCapacity
shippingDetails :: Maybe ShippingDetails
roleARN :: Maybe Text
resources :: Maybe JobResource
remoteManagement :: Maybe RemoteManagement
onDeviceServiceConfiguration :: Maybe OnDeviceServiceConfiguration
notification :: Maybe Notification
longTermPricingId :: Maybe Text
kmsKeyARN :: Maybe Text
jobType :: Maybe JobType
jobState :: Maybe JobState
jobLogInfo :: Maybe JobLogs
jobId :: Maybe Text
forwardingAddressId :: Maybe Text
deviceConfiguration :: Maybe DeviceConfiguration
description :: Maybe Text
dataTransferProgress :: Maybe DataTransfer
creationDate :: Maybe POSIX
clusterId :: Maybe Text
addressId :: Maybe Text
$sel:taxDocuments:JobMetadata' :: JobMetadata -> Maybe TaxDocuments
$sel:snowballType:JobMetadata' :: JobMetadata -> Maybe SnowballType
$sel:snowballCapacityPreference:JobMetadata' :: JobMetadata -> Maybe SnowballCapacity
$sel:shippingDetails:JobMetadata' :: JobMetadata -> Maybe ShippingDetails
$sel:roleARN:JobMetadata' :: JobMetadata -> Maybe Text
$sel:resources:JobMetadata' :: JobMetadata -> Maybe JobResource
$sel:remoteManagement:JobMetadata' :: JobMetadata -> Maybe RemoteManagement
$sel:onDeviceServiceConfiguration:JobMetadata' :: JobMetadata -> Maybe OnDeviceServiceConfiguration
$sel:notification:JobMetadata' :: JobMetadata -> Maybe Notification
$sel:longTermPricingId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:kmsKeyARN:JobMetadata' :: JobMetadata -> Maybe Text
$sel:jobType:JobMetadata' :: JobMetadata -> Maybe JobType
$sel:jobState:JobMetadata' :: JobMetadata -> Maybe JobState
$sel:jobLogInfo:JobMetadata' :: JobMetadata -> Maybe JobLogs
$sel:jobId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:forwardingAddressId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:deviceConfiguration:JobMetadata' :: JobMetadata -> Maybe DeviceConfiguration
$sel:description:JobMetadata' :: JobMetadata -> Maybe Text
$sel:dataTransferProgress:JobMetadata' :: JobMetadata -> Maybe DataTransfer
$sel:creationDate:JobMetadata' :: JobMetadata -> Maybe POSIX
$sel:clusterId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:addressId:JobMetadata' :: JobMetadata -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
addressId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataTransfer
dataTransferProgress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeviceConfiguration
deviceConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
forwardingAddressId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobLogs
jobLogInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobState
jobState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobType
jobType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
longTermPricingId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Notification
notification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RemoteManagement
remoteManagement
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobResource
resources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShippingDetails
shippingDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnowballCapacity
snowballCapacityPreference
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnowballType
snowballType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaxDocuments
taxDocuments

instance Prelude.NFData JobMetadata where
  rnf :: JobMetadata -> ()
rnf JobMetadata' {Maybe Text
Maybe POSIX
Maybe DataTransfer
Maybe JobLogs
Maybe JobState
Maybe JobType
Maybe Notification
Maybe RemoteManagement
Maybe ShippingDetails
Maybe SnowballCapacity
Maybe SnowballType
Maybe OnDeviceServiceConfiguration
Maybe TaxDocuments
Maybe JobResource
Maybe DeviceConfiguration
taxDocuments :: Maybe TaxDocuments
snowballType :: Maybe SnowballType
snowballCapacityPreference :: Maybe SnowballCapacity
shippingDetails :: Maybe ShippingDetails
roleARN :: Maybe Text
resources :: Maybe JobResource
remoteManagement :: Maybe RemoteManagement
onDeviceServiceConfiguration :: Maybe OnDeviceServiceConfiguration
notification :: Maybe Notification
longTermPricingId :: Maybe Text
kmsKeyARN :: Maybe Text
jobType :: Maybe JobType
jobState :: Maybe JobState
jobLogInfo :: Maybe JobLogs
jobId :: Maybe Text
forwardingAddressId :: Maybe Text
deviceConfiguration :: Maybe DeviceConfiguration
description :: Maybe Text
dataTransferProgress :: Maybe DataTransfer
creationDate :: Maybe POSIX
clusterId :: Maybe Text
addressId :: Maybe Text
$sel:taxDocuments:JobMetadata' :: JobMetadata -> Maybe TaxDocuments
$sel:snowballType:JobMetadata' :: JobMetadata -> Maybe SnowballType
$sel:snowballCapacityPreference:JobMetadata' :: JobMetadata -> Maybe SnowballCapacity
$sel:shippingDetails:JobMetadata' :: JobMetadata -> Maybe ShippingDetails
$sel:roleARN:JobMetadata' :: JobMetadata -> Maybe Text
$sel:resources:JobMetadata' :: JobMetadata -> Maybe JobResource
$sel:remoteManagement:JobMetadata' :: JobMetadata -> Maybe RemoteManagement
$sel:onDeviceServiceConfiguration:JobMetadata' :: JobMetadata -> Maybe OnDeviceServiceConfiguration
$sel:notification:JobMetadata' :: JobMetadata -> Maybe Notification
$sel:longTermPricingId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:kmsKeyARN:JobMetadata' :: JobMetadata -> Maybe Text
$sel:jobType:JobMetadata' :: JobMetadata -> Maybe JobType
$sel:jobState:JobMetadata' :: JobMetadata -> Maybe JobState
$sel:jobLogInfo:JobMetadata' :: JobMetadata -> Maybe JobLogs
$sel:jobId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:forwardingAddressId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:deviceConfiguration:JobMetadata' :: JobMetadata -> Maybe DeviceConfiguration
$sel:description:JobMetadata' :: JobMetadata -> Maybe Text
$sel:dataTransferProgress:JobMetadata' :: JobMetadata -> Maybe DataTransfer
$sel:creationDate:JobMetadata' :: JobMetadata -> Maybe POSIX
$sel:clusterId:JobMetadata' :: JobMetadata -> Maybe Text
$sel:addressId:JobMetadata' :: JobMetadata -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
addressId
      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
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataTransfer
dataTransferProgress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceConfiguration
deviceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
forwardingAddressId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobLogs
jobLogInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobState
jobState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobType
jobType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
longTermPricingId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Notification
notification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OnDeviceServiceConfiguration
onDeviceServiceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RemoteManagement
remoteManagement
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobResource
resources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ShippingDetails
shippingDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe SnowballCapacity
snowballCapacityPreference
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SnowballType
snowballType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TaxDocuments
taxDocuments