{-# 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.HealthLake.Types.ImportJobProperties
-- 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.HealthLake.Types.ImportJobProperties where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.HealthLake.Types.InputDataConfig
import Amazonka.HealthLake.Types.JobStatus
import Amazonka.HealthLake.Types.OutputDataConfig
import qualified Amazonka.Prelude as Prelude

-- | Displays the properties of the import job, including the ID, Arn, Name,
-- and the status of the Data Store.
--
-- /See:/ 'newImportJobProperties' smart constructor.
data ImportJobProperties = ImportJobProperties'
  { -- | The Amazon Resource Name (ARN) that gives Amazon HealthLake access to
    -- your input data.
    ImportJobProperties -> Maybe Text
dataAccessRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The time that the Import job was completed.
    ImportJobProperties -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The user-generated name for an Import job.
    ImportJobProperties -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    ImportJobProperties -> Maybe OutputDataConfig
jobOutputDataConfig :: Prelude.Maybe OutputDataConfig,
    -- | An explanation of any errors that may have occurred during the FHIR
    -- import job.
    ImportJobProperties -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | The AWS-generated id number for the Import job.
    ImportJobProperties -> Text
jobId :: Prelude.Text,
    -- | The job status for an Import job. Possible statuses are SUBMITTED,
    -- IN_PROGRESS, COMPLETED, FAILED.
    ImportJobProperties -> JobStatus
jobStatus :: JobStatus,
    -- | The time that the Import job was submitted for processing.
    ImportJobProperties -> POSIX
submitTime :: Data.POSIX,
    -- | The datastore id used when the Import job was created.
    ImportJobProperties -> Text
datastoreId :: Prelude.Text,
    -- | The input data configuration that was supplied when the Import job was
    -- created.
    ImportJobProperties -> InputDataConfig
inputDataConfig :: InputDataConfig
  }
  deriving (ImportJobProperties -> ImportJobProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportJobProperties -> ImportJobProperties -> Bool
$c/= :: ImportJobProperties -> ImportJobProperties -> Bool
== :: ImportJobProperties -> ImportJobProperties -> Bool
$c== :: ImportJobProperties -> ImportJobProperties -> Bool
Prelude.Eq, ReadPrec [ImportJobProperties]
ReadPrec ImportJobProperties
Int -> ReadS ImportJobProperties
ReadS [ImportJobProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportJobProperties]
$creadListPrec :: ReadPrec [ImportJobProperties]
readPrec :: ReadPrec ImportJobProperties
$creadPrec :: ReadPrec ImportJobProperties
readList :: ReadS [ImportJobProperties]
$creadList :: ReadS [ImportJobProperties]
readsPrec :: Int -> ReadS ImportJobProperties
$creadsPrec :: Int -> ReadS ImportJobProperties
Prelude.Read, Int -> ImportJobProperties -> ShowS
[ImportJobProperties] -> ShowS
ImportJobProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportJobProperties] -> ShowS
$cshowList :: [ImportJobProperties] -> ShowS
show :: ImportJobProperties -> String
$cshow :: ImportJobProperties -> String
showsPrec :: Int -> ImportJobProperties -> ShowS
$cshowsPrec :: Int -> ImportJobProperties -> ShowS
Prelude.Show, forall x. Rep ImportJobProperties x -> ImportJobProperties
forall x. ImportJobProperties -> Rep ImportJobProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportJobProperties x -> ImportJobProperties
$cfrom :: forall x. ImportJobProperties -> Rep ImportJobProperties x
Prelude.Generic)

-- |
-- Create a value of 'ImportJobProperties' 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:
--
-- 'dataAccessRoleArn', 'importJobProperties_dataAccessRoleArn' - The Amazon Resource Name (ARN) that gives Amazon HealthLake access to
-- your input data.
--
-- 'endTime', 'importJobProperties_endTime' - The time that the Import job was completed.
--
-- 'jobName', 'importJobProperties_jobName' - The user-generated name for an Import job.
--
-- 'jobOutputDataConfig', 'importJobProperties_jobOutputDataConfig' - Undocumented member.
--
-- 'message', 'importJobProperties_message' - An explanation of any errors that may have occurred during the FHIR
-- import job.
--
-- 'jobId', 'importJobProperties_jobId' - The AWS-generated id number for the Import job.
--
-- 'jobStatus', 'importJobProperties_jobStatus' - The job status for an Import job. Possible statuses are SUBMITTED,
-- IN_PROGRESS, COMPLETED, FAILED.
--
-- 'submitTime', 'importJobProperties_submitTime' - The time that the Import job was submitted for processing.
--
-- 'datastoreId', 'importJobProperties_datastoreId' - The datastore id used when the Import job was created.
--
-- 'inputDataConfig', 'importJobProperties_inputDataConfig' - The input data configuration that was supplied when the Import job was
-- created.
newImportJobProperties ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'jobStatus'
  JobStatus ->
  -- | 'submitTime'
  Prelude.UTCTime ->
  -- | 'datastoreId'
  Prelude.Text ->
  -- | 'inputDataConfig'
  InputDataConfig ->
  ImportJobProperties
newImportJobProperties :: Text
-> JobStatus
-> UTCTime
-> Text
-> InputDataConfig
-> ImportJobProperties
newImportJobProperties
  Text
pJobId_
  JobStatus
pJobStatus_
  UTCTime
pSubmitTime_
  Text
pDatastoreId_
  InputDataConfig
pInputDataConfig_ =
    ImportJobProperties'
      { $sel:dataAccessRoleArn:ImportJobProperties' :: Maybe Text
dataAccessRoleArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:endTime:ImportJobProperties' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:jobName:ImportJobProperties' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
        $sel:jobOutputDataConfig:ImportJobProperties' :: Maybe OutputDataConfig
jobOutputDataConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:message:ImportJobProperties' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
        $sel:jobId:ImportJobProperties' :: Text
jobId = Text
pJobId_,
        $sel:jobStatus:ImportJobProperties' :: JobStatus
jobStatus = JobStatus
pJobStatus_,
        $sel:submitTime:ImportJobProperties' :: POSIX
submitTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pSubmitTime_,
        $sel:datastoreId:ImportJobProperties' :: Text
datastoreId = Text
pDatastoreId_,
        $sel:inputDataConfig:ImportJobProperties' :: InputDataConfig
inputDataConfig = InputDataConfig
pInputDataConfig_
      }

-- | The Amazon Resource Name (ARN) that gives Amazon HealthLake access to
-- your input data.
importJobProperties_dataAccessRoleArn :: Lens.Lens' ImportJobProperties (Prelude.Maybe Prelude.Text)
importJobProperties_dataAccessRoleArn :: Lens' ImportJobProperties (Maybe Text)
importJobProperties_dataAccessRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Maybe Text
dataAccessRoleArn :: Maybe Text
$sel:dataAccessRoleArn:ImportJobProperties' :: ImportJobProperties -> Maybe Text
dataAccessRoleArn} -> Maybe Text
dataAccessRoleArn) (\s :: ImportJobProperties
s@ImportJobProperties' {} Maybe Text
a -> ImportJobProperties
s {$sel:dataAccessRoleArn:ImportJobProperties' :: Maybe Text
dataAccessRoleArn = Maybe Text
a} :: ImportJobProperties)

-- | The time that the Import job was completed.
importJobProperties_endTime :: Lens.Lens' ImportJobProperties (Prelude.Maybe Prelude.UTCTime)
importJobProperties_endTime :: Lens' ImportJobProperties (Maybe UTCTime)
importJobProperties_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:ImportJobProperties' :: ImportJobProperties -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: ImportJobProperties
s@ImportJobProperties' {} Maybe POSIX
a -> ImportJobProperties
s {$sel:endTime:ImportJobProperties' :: Maybe POSIX
endTime = Maybe POSIX
a} :: ImportJobProperties) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The user-generated name for an Import job.
importJobProperties_jobName :: Lens.Lens' ImportJobProperties (Prelude.Maybe Prelude.Text)
importJobProperties_jobName :: Lens' ImportJobProperties (Maybe Text)
importJobProperties_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Maybe Text
jobName :: Maybe Text
$sel:jobName:ImportJobProperties' :: ImportJobProperties -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: ImportJobProperties
s@ImportJobProperties' {} Maybe Text
a -> ImportJobProperties
s {$sel:jobName:ImportJobProperties' :: Maybe Text
jobName = Maybe Text
a} :: ImportJobProperties)

-- | Undocumented member.
importJobProperties_jobOutputDataConfig :: Lens.Lens' ImportJobProperties (Prelude.Maybe OutputDataConfig)
importJobProperties_jobOutputDataConfig :: Lens' ImportJobProperties (Maybe OutputDataConfig)
importJobProperties_jobOutputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Maybe OutputDataConfig
jobOutputDataConfig :: Maybe OutputDataConfig
$sel:jobOutputDataConfig:ImportJobProperties' :: ImportJobProperties -> Maybe OutputDataConfig
jobOutputDataConfig} -> Maybe OutputDataConfig
jobOutputDataConfig) (\s :: ImportJobProperties
s@ImportJobProperties' {} Maybe OutputDataConfig
a -> ImportJobProperties
s {$sel:jobOutputDataConfig:ImportJobProperties' :: Maybe OutputDataConfig
jobOutputDataConfig = Maybe OutputDataConfig
a} :: ImportJobProperties)

-- | An explanation of any errors that may have occurred during the FHIR
-- import job.
importJobProperties_message :: Lens.Lens' ImportJobProperties (Prelude.Maybe Prelude.Text)
importJobProperties_message :: Lens' ImportJobProperties (Maybe Text)
importJobProperties_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Maybe Text
message :: Maybe Text
$sel:message:ImportJobProperties' :: ImportJobProperties -> Maybe Text
message} -> Maybe Text
message) (\s :: ImportJobProperties
s@ImportJobProperties' {} Maybe Text
a -> ImportJobProperties
s {$sel:message:ImportJobProperties' :: Maybe Text
message = Maybe Text
a} :: ImportJobProperties)

-- | The AWS-generated id number for the Import job.
importJobProperties_jobId :: Lens.Lens' ImportJobProperties Prelude.Text
importJobProperties_jobId :: Lens' ImportJobProperties Text
importJobProperties_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Text
jobId :: Text
$sel:jobId:ImportJobProperties' :: ImportJobProperties -> Text
jobId} -> Text
jobId) (\s :: ImportJobProperties
s@ImportJobProperties' {} Text
a -> ImportJobProperties
s {$sel:jobId:ImportJobProperties' :: Text
jobId = Text
a} :: ImportJobProperties)

-- | The job status for an Import job. Possible statuses are SUBMITTED,
-- IN_PROGRESS, COMPLETED, FAILED.
importJobProperties_jobStatus :: Lens.Lens' ImportJobProperties JobStatus
importJobProperties_jobStatus :: Lens' ImportJobProperties JobStatus
importJobProperties_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {JobStatus
jobStatus :: JobStatus
$sel:jobStatus:ImportJobProperties' :: ImportJobProperties -> JobStatus
jobStatus} -> JobStatus
jobStatus) (\s :: ImportJobProperties
s@ImportJobProperties' {} JobStatus
a -> ImportJobProperties
s {$sel:jobStatus:ImportJobProperties' :: JobStatus
jobStatus = JobStatus
a} :: ImportJobProperties)

-- | The time that the Import job was submitted for processing.
importJobProperties_submitTime :: Lens.Lens' ImportJobProperties Prelude.UTCTime
importJobProperties_submitTime :: Lens' ImportJobProperties UTCTime
importJobProperties_submitTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {POSIX
submitTime :: POSIX
$sel:submitTime:ImportJobProperties' :: ImportJobProperties -> POSIX
submitTime} -> POSIX
submitTime) (\s :: ImportJobProperties
s@ImportJobProperties' {} POSIX
a -> ImportJobProperties
s {$sel:submitTime:ImportJobProperties' :: POSIX
submitTime = POSIX
a} :: ImportJobProperties) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The datastore id used when the Import job was created.
importJobProperties_datastoreId :: Lens.Lens' ImportJobProperties Prelude.Text
importJobProperties_datastoreId :: Lens' ImportJobProperties Text
importJobProperties_datastoreId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {Text
datastoreId :: Text
$sel:datastoreId:ImportJobProperties' :: ImportJobProperties -> Text
datastoreId} -> Text
datastoreId) (\s :: ImportJobProperties
s@ImportJobProperties' {} Text
a -> ImportJobProperties
s {$sel:datastoreId:ImportJobProperties' :: Text
datastoreId = Text
a} :: ImportJobProperties)

-- | The input data configuration that was supplied when the Import job was
-- created.
importJobProperties_inputDataConfig :: Lens.Lens' ImportJobProperties InputDataConfig
importJobProperties_inputDataConfig :: Lens' ImportJobProperties InputDataConfig
importJobProperties_inputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportJobProperties' {InputDataConfig
inputDataConfig :: InputDataConfig
$sel:inputDataConfig:ImportJobProperties' :: ImportJobProperties -> InputDataConfig
inputDataConfig} -> InputDataConfig
inputDataConfig) (\s :: ImportJobProperties
s@ImportJobProperties' {} InputDataConfig
a -> ImportJobProperties
s {$sel:inputDataConfig:ImportJobProperties' :: InputDataConfig
inputDataConfig = InputDataConfig
a} :: ImportJobProperties)

instance Data.FromJSON ImportJobProperties where
  parseJSON :: Value -> Parser ImportJobProperties
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ImportJobProperties"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe OutputDataConfig
-> Maybe Text
-> Text
-> JobStatus
-> POSIX
-> Text
-> InputDataConfig
-> ImportJobProperties
ImportJobProperties'
            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
"DataAccessRoleArn")
            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
"EndTime")
            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
"JobName")
            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
"JobOutputDataConfig")
            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
"Message")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"JobId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"JobStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SubmitTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DatastoreId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"InputDataConfig")
      )

instance Prelude.Hashable ImportJobProperties where
  hashWithSalt :: Int -> ImportJobProperties -> Int
hashWithSalt Int
_salt ImportJobProperties' {Maybe Text
Maybe POSIX
Maybe OutputDataConfig
Text
POSIX
InputDataConfig
JobStatus
inputDataConfig :: InputDataConfig
datastoreId :: Text
submitTime :: POSIX
jobStatus :: JobStatus
jobId :: Text
message :: Maybe Text
jobOutputDataConfig :: Maybe OutputDataConfig
jobName :: Maybe Text
endTime :: Maybe POSIX
dataAccessRoleArn :: Maybe Text
$sel:inputDataConfig:ImportJobProperties' :: ImportJobProperties -> InputDataConfig
$sel:datastoreId:ImportJobProperties' :: ImportJobProperties -> Text
$sel:submitTime:ImportJobProperties' :: ImportJobProperties -> POSIX
$sel:jobStatus:ImportJobProperties' :: ImportJobProperties -> JobStatus
$sel:jobId:ImportJobProperties' :: ImportJobProperties -> Text
$sel:message:ImportJobProperties' :: ImportJobProperties -> Maybe Text
$sel:jobOutputDataConfig:ImportJobProperties' :: ImportJobProperties -> Maybe OutputDataConfig
$sel:jobName:ImportJobProperties' :: ImportJobProperties -> Maybe Text
$sel:endTime:ImportJobProperties' :: ImportJobProperties -> Maybe POSIX
$sel:dataAccessRoleArn:ImportJobProperties' :: ImportJobProperties -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataAccessRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputDataConfig
jobOutputDataConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
message
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` JobStatus
jobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
submitTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
datastoreId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InputDataConfig
inputDataConfig

instance Prelude.NFData ImportJobProperties where
  rnf :: ImportJobProperties -> ()
rnf ImportJobProperties' {Maybe Text
Maybe POSIX
Maybe OutputDataConfig
Text
POSIX
InputDataConfig
JobStatus
inputDataConfig :: InputDataConfig
datastoreId :: Text
submitTime :: POSIX
jobStatus :: JobStatus
jobId :: Text
message :: Maybe Text
jobOutputDataConfig :: Maybe OutputDataConfig
jobName :: Maybe Text
endTime :: Maybe POSIX
dataAccessRoleArn :: Maybe Text
$sel:inputDataConfig:ImportJobProperties' :: ImportJobProperties -> InputDataConfig
$sel:datastoreId:ImportJobProperties' :: ImportJobProperties -> Text
$sel:submitTime:ImportJobProperties' :: ImportJobProperties -> POSIX
$sel:jobStatus:ImportJobProperties' :: ImportJobProperties -> JobStatus
$sel:jobId:ImportJobProperties' :: ImportJobProperties -> Text
$sel:message:ImportJobProperties' :: ImportJobProperties -> Maybe Text
$sel:jobOutputDataConfig:ImportJobProperties' :: ImportJobProperties -> Maybe OutputDataConfig
$sel:jobName:ImportJobProperties' :: ImportJobProperties -> Maybe Text
$sel:endTime:ImportJobProperties' :: ImportJobProperties -> Maybe POSIX
$sel:dataAccessRoleArn:ImportJobProperties' :: ImportJobProperties -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataAccessRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputDataConfig
jobOutputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JobStatus
jobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
submitTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
datastoreId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InputDataConfig
inputDataConfig