{-# 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.Kendra.Types.DataSourceSyncJob
-- 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.Kendra.Types.DataSourceSyncJob where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kendra.Types.DataSourceSyncJobMetrics
import Amazonka.Kendra.Types.DataSourceSyncJobStatus
import Amazonka.Kendra.Types.ErrorCode
import qualified Amazonka.Prelude as Prelude

-- | Provides information about a data source synchronization job.
--
-- /See:/ 'newDataSourceSyncJob' smart constructor.
data DataSourceSyncJob = DataSourceSyncJob'
  { -- | If the reason that the synchronization failed is due to an error with
    -- the underlying data source, this field contains a code that identifies
    -- the error.
    DataSourceSyncJob -> Maybe Text
dataSourceErrorCode :: Prelude.Maybe Prelude.Text,
    -- | The UNIX datetime that the synchronization job completed.
    DataSourceSyncJob -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | If the @Status@ field is set to @FAILED@, the @ErrorCode@ field
    -- indicates the reason the synchronization failed.
    DataSourceSyncJob -> Maybe ErrorCode
errorCode :: Prelude.Maybe ErrorCode,
    -- | If the @Status@ field is set to @ERROR@, the @ErrorMessage@ field
    -- contains a description of the error that caused the synchronization to
    -- fail.
    DataSourceSyncJob -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | A identifier for the synchronization job.
    DataSourceSyncJob -> Maybe Text
executionId :: Prelude.Maybe Prelude.Text,
    -- | Maps a batch delete document request to a specific data source sync job.
    -- This is optional and should only be supplied when documents are deleted
    -- by a data source connector.
    DataSourceSyncJob -> Maybe DataSourceSyncJobMetrics
metrics :: Prelude.Maybe DataSourceSyncJobMetrics,
    -- | The UNIX datetime that the synchronization job started.
    DataSourceSyncJob -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The execution status of the synchronization job. When the @Status@ field
    -- is set to @SUCCEEDED@, the synchronization job is done. If the status
    -- code is set to @FAILED@, the @ErrorCode@ and @ErrorMessage@ fields give
    -- you the reason for the failure.
    DataSourceSyncJob -> Maybe DataSourceSyncJobStatus
status :: Prelude.Maybe DataSourceSyncJobStatus
  }
  deriving (DataSourceSyncJob -> DataSourceSyncJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataSourceSyncJob -> DataSourceSyncJob -> Bool
$c/= :: DataSourceSyncJob -> DataSourceSyncJob -> Bool
== :: DataSourceSyncJob -> DataSourceSyncJob -> Bool
$c== :: DataSourceSyncJob -> DataSourceSyncJob -> Bool
Prelude.Eq, ReadPrec [DataSourceSyncJob]
ReadPrec DataSourceSyncJob
Int -> ReadS DataSourceSyncJob
ReadS [DataSourceSyncJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataSourceSyncJob]
$creadListPrec :: ReadPrec [DataSourceSyncJob]
readPrec :: ReadPrec DataSourceSyncJob
$creadPrec :: ReadPrec DataSourceSyncJob
readList :: ReadS [DataSourceSyncJob]
$creadList :: ReadS [DataSourceSyncJob]
readsPrec :: Int -> ReadS DataSourceSyncJob
$creadsPrec :: Int -> ReadS DataSourceSyncJob
Prelude.Read, Int -> DataSourceSyncJob -> ShowS
[DataSourceSyncJob] -> ShowS
DataSourceSyncJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataSourceSyncJob] -> ShowS
$cshowList :: [DataSourceSyncJob] -> ShowS
show :: DataSourceSyncJob -> String
$cshow :: DataSourceSyncJob -> String
showsPrec :: Int -> DataSourceSyncJob -> ShowS
$cshowsPrec :: Int -> DataSourceSyncJob -> ShowS
Prelude.Show, forall x. Rep DataSourceSyncJob x -> DataSourceSyncJob
forall x. DataSourceSyncJob -> Rep DataSourceSyncJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataSourceSyncJob x -> DataSourceSyncJob
$cfrom :: forall x. DataSourceSyncJob -> Rep DataSourceSyncJob x
Prelude.Generic)

-- |
-- Create a value of 'DataSourceSyncJob' 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:
--
-- 'dataSourceErrorCode', 'dataSourceSyncJob_dataSourceErrorCode' - If the reason that the synchronization failed is due to an error with
-- the underlying data source, this field contains a code that identifies
-- the error.
--
-- 'endTime', 'dataSourceSyncJob_endTime' - The UNIX datetime that the synchronization job completed.
--
-- 'errorCode', 'dataSourceSyncJob_errorCode' - If the @Status@ field is set to @FAILED@, the @ErrorCode@ field
-- indicates the reason the synchronization failed.
--
-- 'errorMessage', 'dataSourceSyncJob_errorMessage' - If the @Status@ field is set to @ERROR@, the @ErrorMessage@ field
-- contains a description of the error that caused the synchronization to
-- fail.
--
-- 'executionId', 'dataSourceSyncJob_executionId' - A identifier for the synchronization job.
--
-- 'metrics', 'dataSourceSyncJob_metrics' - Maps a batch delete document request to a specific data source sync job.
-- This is optional and should only be supplied when documents are deleted
-- by a data source connector.
--
-- 'startTime', 'dataSourceSyncJob_startTime' - The UNIX datetime that the synchronization job started.
--
-- 'status', 'dataSourceSyncJob_status' - The execution status of the synchronization job. When the @Status@ field
-- is set to @SUCCEEDED@, the synchronization job is done. If the status
-- code is set to @FAILED@, the @ErrorCode@ and @ErrorMessage@ fields give
-- you the reason for the failure.
newDataSourceSyncJob ::
  DataSourceSyncJob
newDataSourceSyncJob :: DataSourceSyncJob
newDataSourceSyncJob =
  DataSourceSyncJob'
    { $sel:dataSourceErrorCode:DataSourceSyncJob' :: Maybe Text
dataSourceErrorCode =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:DataSourceSyncJob' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:errorCode:DataSourceSyncJob' :: Maybe ErrorCode
errorCode = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:DataSourceSyncJob' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:executionId:DataSourceSyncJob' :: Maybe Text
executionId = forall a. Maybe a
Prelude.Nothing,
      $sel:metrics:DataSourceSyncJob' :: Maybe DataSourceSyncJobMetrics
metrics = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:DataSourceSyncJob' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DataSourceSyncJob' :: Maybe DataSourceSyncJobStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | If the reason that the synchronization failed is due to an error with
-- the underlying data source, this field contains a code that identifies
-- the error.
dataSourceSyncJob_dataSourceErrorCode :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe Prelude.Text)
dataSourceSyncJob_dataSourceErrorCode :: Lens' DataSourceSyncJob (Maybe Text)
dataSourceSyncJob_dataSourceErrorCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe Text
dataSourceErrorCode :: Maybe Text
$sel:dataSourceErrorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
dataSourceErrorCode} -> Maybe Text
dataSourceErrorCode) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe Text
a -> DataSourceSyncJob
s {$sel:dataSourceErrorCode:DataSourceSyncJob' :: Maybe Text
dataSourceErrorCode = Maybe Text
a} :: DataSourceSyncJob)

-- | The UNIX datetime that the synchronization job completed.
dataSourceSyncJob_endTime :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe Prelude.UTCTime)
dataSourceSyncJob_endTime :: Lens' DataSourceSyncJob (Maybe UTCTime)
dataSourceSyncJob_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe POSIX
a -> DataSourceSyncJob
s {$sel:endTime:DataSourceSyncJob' :: Maybe POSIX
endTime = Maybe POSIX
a} :: DataSourceSyncJob) 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

-- | If the @Status@ field is set to @FAILED@, the @ErrorCode@ field
-- indicates the reason the synchronization failed.
dataSourceSyncJob_errorCode :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe ErrorCode)
dataSourceSyncJob_errorCode :: Lens' DataSourceSyncJob (Maybe ErrorCode)
dataSourceSyncJob_errorCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe ErrorCode
errorCode :: Maybe ErrorCode
$sel:errorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe ErrorCode
errorCode} -> Maybe ErrorCode
errorCode) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe ErrorCode
a -> DataSourceSyncJob
s {$sel:errorCode:DataSourceSyncJob' :: Maybe ErrorCode
errorCode = Maybe ErrorCode
a} :: DataSourceSyncJob)

-- | If the @Status@ field is set to @ERROR@, the @ErrorMessage@ field
-- contains a description of the error that caused the synchronization to
-- fail.
dataSourceSyncJob_errorMessage :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe Prelude.Text)
dataSourceSyncJob_errorMessage :: Lens' DataSourceSyncJob (Maybe Text)
dataSourceSyncJob_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe Text
a -> DataSourceSyncJob
s {$sel:errorMessage:DataSourceSyncJob' :: Maybe Text
errorMessage = Maybe Text
a} :: DataSourceSyncJob)

-- | A identifier for the synchronization job.
dataSourceSyncJob_executionId :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe Prelude.Text)
dataSourceSyncJob_executionId :: Lens' DataSourceSyncJob (Maybe Text)
dataSourceSyncJob_executionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe Text
executionId :: Maybe Text
$sel:executionId:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
executionId} -> Maybe Text
executionId) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe Text
a -> DataSourceSyncJob
s {$sel:executionId:DataSourceSyncJob' :: Maybe Text
executionId = Maybe Text
a} :: DataSourceSyncJob)

-- | Maps a batch delete document request to a specific data source sync job.
-- This is optional and should only be supplied when documents are deleted
-- by a data source connector.
dataSourceSyncJob_metrics :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe DataSourceSyncJobMetrics)
dataSourceSyncJob_metrics :: Lens' DataSourceSyncJob (Maybe DataSourceSyncJobMetrics)
dataSourceSyncJob_metrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe DataSourceSyncJobMetrics
metrics :: Maybe DataSourceSyncJobMetrics
$sel:metrics:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobMetrics
metrics} -> Maybe DataSourceSyncJobMetrics
metrics) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe DataSourceSyncJobMetrics
a -> DataSourceSyncJob
s {$sel:metrics:DataSourceSyncJob' :: Maybe DataSourceSyncJobMetrics
metrics = Maybe DataSourceSyncJobMetrics
a} :: DataSourceSyncJob)

-- | The UNIX datetime that the synchronization job started.
dataSourceSyncJob_startTime :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe Prelude.UTCTime)
dataSourceSyncJob_startTime :: Lens' DataSourceSyncJob (Maybe UTCTime)
dataSourceSyncJob_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe POSIX
a -> DataSourceSyncJob
s {$sel:startTime:DataSourceSyncJob' :: Maybe POSIX
startTime = Maybe POSIX
a} :: DataSourceSyncJob) 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 execution status of the synchronization job. When the @Status@ field
-- is set to @SUCCEEDED@, the synchronization job is done. If the status
-- code is set to @FAILED@, the @ErrorCode@ and @ErrorMessage@ fields give
-- you the reason for the failure.
dataSourceSyncJob_status :: Lens.Lens' DataSourceSyncJob (Prelude.Maybe DataSourceSyncJobStatus)
dataSourceSyncJob_status :: Lens' DataSourceSyncJob (Maybe DataSourceSyncJobStatus)
dataSourceSyncJob_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSourceSyncJob' {Maybe DataSourceSyncJobStatus
status :: Maybe DataSourceSyncJobStatus
$sel:status:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobStatus
status} -> Maybe DataSourceSyncJobStatus
status) (\s :: DataSourceSyncJob
s@DataSourceSyncJob' {} Maybe DataSourceSyncJobStatus
a -> DataSourceSyncJob
s {$sel:status:DataSourceSyncJob' :: Maybe DataSourceSyncJobStatus
status = Maybe DataSourceSyncJobStatus
a} :: DataSourceSyncJob)

instance Data.FromJSON DataSourceSyncJob where
  parseJSON :: Value -> Parser DataSourceSyncJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DataSourceSyncJob"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe ErrorCode
-> Maybe Text
-> Maybe Text
-> Maybe DataSourceSyncJobMetrics
-> Maybe POSIX
-> Maybe DataSourceSyncJobStatus
-> DataSourceSyncJob
DataSourceSyncJob'
            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
"DataSourceErrorCode")
            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
"ErrorCode")
            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
"ErrorMessage")
            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
"ExecutionId")
            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
"Metrics")
            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
"StartTime")
            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
"Status")
      )

instance Prelude.Hashable DataSourceSyncJob where
  hashWithSalt :: Int -> DataSourceSyncJob -> Int
hashWithSalt Int
_salt DataSourceSyncJob' {Maybe Text
Maybe POSIX
Maybe DataSourceSyncJobMetrics
Maybe DataSourceSyncJobStatus
Maybe ErrorCode
status :: Maybe DataSourceSyncJobStatus
startTime :: Maybe POSIX
metrics :: Maybe DataSourceSyncJobMetrics
executionId :: Maybe Text
errorMessage :: Maybe Text
errorCode :: Maybe ErrorCode
endTime :: Maybe POSIX
dataSourceErrorCode :: Maybe Text
$sel:status:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobStatus
$sel:startTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
$sel:metrics:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobMetrics
$sel:executionId:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
$sel:errorMessage:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
$sel:errorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe ErrorCode
$sel:endTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
$sel:dataSourceErrorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataSourceErrorCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ErrorCode
errorCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
errorMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataSourceSyncJobMetrics
metrics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataSourceSyncJobStatus
status

instance Prelude.NFData DataSourceSyncJob where
  rnf :: DataSourceSyncJob -> ()
rnf DataSourceSyncJob' {Maybe Text
Maybe POSIX
Maybe DataSourceSyncJobMetrics
Maybe DataSourceSyncJobStatus
Maybe ErrorCode
status :: Maybe DataSourceSyncJobStatus
startTime :: Maybe POSIX
metrics :: Maybe DataSourceSyncJobMetrics
executionId :: Maybe Text
errorMessage :: Maybe Text
errorCode :: Maybe ErrorCode
endTime :: Maybe POSIX
dataSourceErrorCode :: Maybe Text
$sel:status:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobStatus
$sel:startTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
$sel:metrics:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe DataSourceSyncJobMetrics
$sel:executionId:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
$sel:errorMessage:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
$sel:errorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe ErrorCode
$sel:endTime:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe POSIX
$sel:dataSourceErrorCode:DataSourceSyncJob' :: DataSourceSyncJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataSourceErrorCode
      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 ErrorCode
errorCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceSyncJobMetrics
metrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceSyncJobStatus
status