{-# 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.Personalize.Types.BatchInferenceJob
-- 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.Personalize.Types.BatchInferenceJob where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Personalize.Types.BatchInferenceJobConfig
import Amazonka.Personalize.Types.BatchInferenceJobInput
import Amazonka.Personalize.Types.BatchInferenceJobOutput
import qualified Amazonka.Prelude as Prelude

-- | Contains information on a batch inference job.
--
-- /See:/ 'newBatchInferenceJob' smart constructor.
data BatchInferenceJob = BatchInferenceJob'
  { -- | The Amazon Resource Name (ARN) of the batch inference job.
    BatchInferenceJob -> Maybe Text
batchInferenceJobArn :: Prelude.Maybe Prelude.Text,
    -- | A string to string map of the configuration details of a batch inference
    -- job.
    BatchInferenceJob -> Maybe BatchInferenceJobConfig
batchInferenceJobConfig :: Prelude.Maybe BatchInferenceJobConfig,
    -- | The time at which the batch inference job was created.
    BatchInferenceJob -> Maybe POSIX
creationDateTime :: Prelude.Maybe Data.POSIX,
    -- | If the batch inference job failed, the reason for the failure.
    BatchInferenceJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the filter used on the batch inference job.
    BatchInferenceJob -> Maybe Text
filterArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 path that leads to the input data used to generate the
    -- batch inference job.
    BatchInferenceJob -> Maybe BatchInferenceJobInput
jobInput :: Prelude.Maybe BatchInferenceJobInput,
    -- | The name of the batch inference job.
    BatchInferenceJob -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 bucket that contains the output data generated by the
    -- batch inference job.
    BatchInferenceJob -> Maybe BatchInferenceJobOutput
jobOutput :: Prelude.Maybe BatchInferenceJobOutput,
    -- | The time at which the batch inference job was last updated.
    BatchInferenceJob -> Maybe POSIX
lastUpdatedDateTime :: Prelude.Maybe Data.POSIX,
    -- | The number of recommendations generated by the batch inference job. This
    -- number includes the error messages generated for failed input records.
    BatchInferenceJob -> Maybe Int
numResults :: Prelude.Maybe Prelude.Int,
    -- | The ARN of the Amazon Identity and Access Management (IAM) role that
    -- requested the batch inference job.
    BatchInferenceJob -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the solution version from which the
    -- batch inference job was created.
    BatchInferenceJob -> Maybe Text
solutionVersionArn :: Prelude.Maybe Prelude.Text,
    -- | The status of the batch inference job. The status is one of the
    -- following values:
    --
    -- -   PENDING
    --
    -- -   IN PROGRESS
    --
    -- -   ACTIVE
    --
    -- -   CREATE FAILED
    BatchInferenceJob -> Maybe Text
status :: Prelude.Maybe Prelude.Text
  }
  deriving (BatchInferenceJob -> BatchInferenceJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchInferenceJob -> BatchInferenceJob -> Bool
$c/= :: BatchInferenceJob -> BatchInferenceJob -> Bool
== :: BatchInferenceJob -> BatchInferenceJob -> Bool
$c== :: BatchInferenceJob -> BatchInferenceJob -> Bool
Prelude.Eq, ReadPrec [BatchInferenceJob]
ReadPrec BatchInferenceJob
Int -> ReadS BatchInferenceJob
ReadS [BatchInferenceJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchInferenceJob]
$creadListPrec :: ReadPrec [BatchInferenceJob]
readPrec :: ReadPrec BatchInferenceJob
$creadPrec :: ReadPrec BatchInferenceJob
readList :: ReadS [BatchInferenceJob]
$creadList :: ReadS [BatchInferenceJob]
readsPrec :: Int -> ReadS BatchInferenceJob
$creadsPrec :: Int -> ReadS BatchInferenceJob
Prelude.Read, Int -> BatchInferenceJob -> ShowS
[BatchInferenceJob] -> ShowS
BatchInferenceJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchInferenceJob] -> ShowS
$cshowList :: [BatchInferenceJob] -> ShowS
show :: BatchInferenceJob -> String
$cshow :: BatchInferenceJob -> String
showsPrec :: Int -> BatchInferenceJob -> ShowS
$cshowsPrec :: Int -> BatchInferenceJob -> ShowS
Prelude.Show, forall x. Rep BatchInferenceJob x -> BatchInferenceJob
forall x. BatchInferenceJob -> Rep BatchInferenceJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchInferenceJob x -> BatchInferenceJob
$cfrom :: forall x. BatchInferenceJob -> Rep BatchInferenceJob x
Prelude.Generic)

-- |
-- Create a value of 'BatchInferenceJob' 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:
--
-- 'batchInferenceJobArn', 'batchInferenceJob_batchInferenceJobArn' - The Amazon Resource Name (ARN) of the batch inference job.
--
-- 'batchInferenceJobConfig', 'batchInferenceJob_batchInferenceJobConfig' - A string to string map of the configuration details of a batch inference
-- job.
--
-- 'creationDateTime', 'batchInferenceJob_creationDateTime' - The time at which the batch inference job was created.
--
-- 'failureReason', 'batchInferenceJob_failureReason' - If the batch inference job failed, the reason for the failure.
--
-- 'filterArn', 'batchInferenceJob_filterArn' - The ARN of the filter used on the batch inference job.
--
-- 'jobInput', 'batchInferenceJob_jobInput' - The Amazon S3 path that leads to the input data used to generate the
-- batch inference job.
--
-- 'jobName', 'batchInferenceJob_jobName' - The name of the batch inference job.
--
-- 'jobOutput', 'batchInferenceJob_jobOutput' - The Amazon S3 bucket that contains the output data generated by the
-- batch inference job.
--
-- 'lastUpdatedDateTime', 'batchInferenceJob_lastUpdatedDateTime' - The time at which the batch inference job was last updated.
--
-- 'numResults', 'batchInferenceJob_numResults' - The number of recommendations generated by the batch inference job. This
-- number includes the error messages generated for failed input records.
--
-- 'roleArn', 'batchInferenceJob_roleArn' - The ARN of the Amazon Identity and Access Management (IAM) role that
-- requested the batch inference job.
--
-- 'solutionVersionArn', 'batchInferenceJob_solutionVersionArn' - The Amazon Resource Name (ARN) of the solution version from which the
-- batch inference job was created.
--
-- 'status', 'batchInferenceJob_status' - The status of the batch inference job. The status is one of the
-- following values:
--
-- -   PENDING
--
-- -   IN PROGRESS
--
-- -   ACTIVE
--
-- -   CREATE FAILED
newBatchInferenceJob ::
  BatchInferenceJob
newBatchInferenceJob :: BatchInferenceJob
newBatchInferenceJob =
  BatchInferenceJob'
    { $sel:batchInferenceJobArn:BatchInferenceJob' :: Maybe Text
batchInferenceJobArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:batchInferenceJobConfig:BatchInferenceJob' :: Maybe BatchInferenceJobConfig
batchInferenceJobConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDateTime:BatchInferenceJob' :: Maybe POSIX
creationDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:BatchInferenceJob' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:filterArn:BatchInferenceJob' :: Maybe Text
filterArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobInput:BatchInferenceJob' :: Maybe BatchInferenceJobInput
jobInput = forall a. Maybe a
Prelude.Nothing,
      $sel:jobName:BatchInferenceJob' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
      $sel:jobOutput:BatchInferenceJob' :: Maybe BatchInferenceJobOutput
jobOutput = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDateTime:BatchInferenceJob' :: Maybe POSIX
lastUpdatedDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:numResults:BatchInferenceJob' :: Maybe Int
numResults = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:BatchInferenceJob' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:solutionVersionArn:BatchInferenceJob' :: Maybe Text
solutionVersionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:BatchInferenceJob' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the batch inference job.
batchInferenceJob_batchInferenceJobArn :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_batchInferenceJobArn :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_batchInferenceJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
batchInferenceJobArn :: Maybe Text
$sel:batchInferenceJobArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
batchInferenceJobArn} -> Maybe Text
batchInferenceJobArn) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:batchInferenceJobArn:BatchInferenceJob' :: Maybe Text
batchInferenceJobArn = Maybe Text
a} :: BatchInferenceJob)

-- | A string to string map of the configuration details of a batch inference
-- job.
batchInferenceJob_batchInferenceJobConfig :: Lens.Lens' BatchInferenceJob (Prelude.Maybe BatchInferenceJobConfig)
batchInferenceJob_batchInferenceJobConfig :: Lens' BatchInferenceJob (Maybe BatchInferenceJobConfig)
batchInferenceJob_batchInferenceJobConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe BatchInferenceJobConfig
batchInferenceJobConfig :: Maybe BatchInferenceJobConfig
$sel:batchInferenceJobConfig:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobConfig
batchInferenceJobConfig} -> Maybe BatchInferenceJobConfig
batchInferenceJobConfig) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe BatchInferenceJobConfig
a -> BatchInferenceJob
s {$sel:batchInferenceJobConfig:BatchInferenceJob' :: Maybe BatchInferenceJobConfig
batchInferenceJobConfig = Maybe BatchInferenceJobConfig
a} :: BatchInferenceJob)

-- | The time at which the batch inference job was created.
batchInferenceJob_creationDateTime :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.UTCTime)
batchInferenceJob_creationDateTime :: Lens' BatchInferenceJob (Maybe UTCTime)
batchInferenceJob_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe POSIX
creationDateTime :: Maybe POSIX
$sel:creationDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
creationDateTime} -> Maybe POSIX
creationDateTime) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe POSIX
a -> BatchInferenceJob
s {$sel:creationDateTime:BatchInferenceJob' :: Maybe POSIX
creationDateTime = Maybe POSIX
a} :: BatchInferenceJob) 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 batch inference job failed, the reason for the failure.
batchInferenceJob_failureReason :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_failureReason :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:failureReason:BatchInferenceJob' :: Maybe Text
failureReason = Maybe Text
a} :: BatchInferenceJob)

-- | The ARN of the filter used on the batch inference job.
batchInferenceJob_filterArn :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_filterArn :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_filterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
filterArn :: Maybe Text
$sel:filterArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
filterArn} -> Maybe Text
filterArn) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:filterArn:BatchInferenceJob' :: Maybe Text
filterArn = Maybe Text
a} :: BatchInferenceJob)

-- | The Amazon S3 path that leads to the input data used to generate the
-- batch inference job.
batchInferenceJob_jobInput :: Lens.Lens' BatchInferenceJob (Prelude.Maybe BatchInferenceJobInput)
batchInferenceJob_jobInput :: Lens' BatchInferenceJob (Maybe BatchInferenceJobInput)
batchInferenceJob_jobInput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe BatchInferenceJobInput
jobInput :: Maybe BatchInferenceJobInput
$sel:jobInput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobInput
jobInput} -> Maybe BatchInferenceJobInput
jobInput) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe BatchInferenceJobInput
a -> BatchInferenceJob
s {$sel:jobInput:BatchInferenceJob' :: Maybe BatchInferenceJobInput
jobInput = Maybe BatchInferenceJobInput
a} :: BatchInferenceJob)

-- | The name of the batch inference job.
batchInferenceJob_jobName :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_jobName :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
jobName :: Maybe Text
$sel:jobName:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:jobName:BatchInferenceJob' :: Maybe Text
jobName = Maybe Text
a} :: BatchInferenceJob)

-- | The Amazon S3 bucket that contains the output data generated by the
-- batch inference job.
batchInferenceJob_jobOutput :: Lens.Lens' BatchInferenceJob (Prelude.Maybe BatchInferenceJobOutput)
batchInferenceJob_jobOutput :: Lens' BatchInferenceJob (Maybe BatchInferenceJobOutput)
batchInferenceJob_jobOutput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe BatchInferenceJobOutput
jobOutput :: Maybe BatchInferenceJobOutput
$sel:jobOutput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobOutput
jobOutput} -> Maybe BatchInferenceJobOutput
jobOutput) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe BatchInferenceJobOutput
a -> BatchInferenceJob
s {$sel:jobOutput:BatchInferenceJob' :: Maybe BatchInferenceJobOutput
jobOutput = Maybe BatchInferenceJobOutput
a} :: BatchInferenceJob)

-- | The time at which the batch inference job was last updated.
batchInferenceJob_lastUpdatedDateTime :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.UTCTime)
batchInferenceJob_lastUpdatedDateTime :: Lens' BatchInferenceJob (Maybe UTCTime)
batchInferenceJob_lastUpdatedDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe POSIX
lastUpdatedDateTime :: Maybe POSIX
$sel:lastUpdatedDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
lastUpdatedDateTime} -> Maybe POSIX
lastUpdatedDateTime) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe POSIX
a -> BatchInferenceJob
s {$sel:lastUpdatedDateTime:BatchInferenceJob' :: Maybe POSIX
lastUpdatedDateTime = Maybe POSIX
a} :: BatchInferenceJob) 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 number of recommendations generated by the batch inference job. This
-- number includes the error messages generated for failed input records.
batchInferenceJob_numResults :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Int)
batchInferenceJob_numResults :: Lens' BatchInferenceJob (Maybe Int)
batchInferenceJob_numResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Int
numResults :: Maybe Int
$sel:numResults:BatchInferenceJob' :: BatchInferenceJob -> Maybe Int
numResults} -> Maybe Int
numResults) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Int
a -> BatchInferenceJob
s {$sel:numResults:BatchInferenceJob' :: Maybe Int
numResults = Maybe Int
a} :: BatchInferenceJob)

-- | The ARN of the Amazon Identity and Access Management (IAM) role that
-- requested the batch inference job.
batchInferenceJob_roleArn :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_roleArn :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:roleArn:BatchInferenceJob' :: Maybe Text
roleArn = Maybe Text
a} :: BatchInferenceJob)

-- | The Amazon Resource Name (ARN) of the solution version from which the
-- batch inference job was created.
batchInferenceJob_solutionVersionArn :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_solutionVersionArn :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_solutionVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
solutionVersionArn :: Maybe Text
$sel:solutionVersionArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
solutionVersionArn} -> Maybe Text
solutionVersionArn) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:solutionVersionArn:BatchInferenceJob' :: Maybe Text
solutionVersionArn = Maybe Text
a} :: BatchInferenceJob)

-- | The status of the batch inference job. The status is one of the
-- following values:
--
-- -   PENDING
--
-- -   IN PROGRESS
--
-- -   ACTIVE
--
-- -   CREATE FAILED
batchInferenceJob_status :: Lens.Lens' BatchInferenceJob (Prelude.Maybe Prelude.Text)
batchInferenceJob_status :: Lens' BatchInferenceJob (Maybe Text)
batchInferenceJob_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchInferenceJob' {Maybe Text
status :: Maybe Text
$sel:status:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
status} -> Maybe Text
status) (\s :: BatchInferenceJob
s@BatchInferenceJob' {} Maybe Text
a -> BatchInferenceJob
s {$sel:status:BatchInferenceJob' :: Maybe Text
status = Maybe Text
a} :: BatchInferenceJob)

instance Data.FromJSON BatchInferenceJob where
  parseJSON :: Value -> Parser BatchInferenceJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"BatchInferenceJob"
      ( \Object
x ->
          Maybe Text
-> Maybe BatchInferenceJobConfig
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe BatchInferenceJobInput
-> Maybe Text
-> Maybe BatchInferenceJobOutput
-> Maybe POSIX
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> BatchInferenceJob
BatchInferenceJob'
            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
"batchInferenceJobArn")
            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
"batchInferenceJobConfig")
            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
"creationDateTime")
            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
"failureReason")
            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
"filterArn")
            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
"jobInput")
            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
"jobOutput")
            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
"lastUpdatedDateTime")
            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
"numResults")
            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
"solutionVersionArn")
            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 BatchInferenceJob where
  hashWithSalt :: Int -> BatchInferenceJob -> Int
hashWithSalt Int
_salt BatchInferenceJob' {Maybe Int
Maybe Text
Maybe POSIX
Maybe BatchInferenceJobConfig
Maybe BatchInferenceJobOutput
Maybe BatchInferenceJobInput
status :: Maybe Text
solutionVersionArn :: Maybe Text
roleArn :: Maybe Text
numResults :: Maybe Int
lastUpdatedDateTime :: Maybe POSIX
jobOutput :: Maybe BatchInferenceJobOutput
jobName :: Maybe Text
jobInput :: Maybe BatchInferenceJobInput
filterArn :: Maybe Text
failureReason :: Maybe Text
creationDateTime :: Maybe POSIX
batchInferenceJobConfig :: Maybe BatchInferenceJobConfig
batchInferenceJobArn :: Maybe Text
$sel:status:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:solutionVersionArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:roleArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:numResults:BatchInferenceJob' :: BatchInferenceJob -> Maybe Int
$sel:lastUpdatedDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
$sel:jobOutput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobOutput
$sel:jobName:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:jobInput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobInput
$sel:filterArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:failureReason:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:creationDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
$sel:batchInferenceJobConfig:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobConfig
$sel:batchInferenceJobArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
batchInferenceJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BatchInferenceJobConfig
batchInferenceJobConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BatchInferenceJobInput
jobInput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BatchInferenceJobOutput
jobOutput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
solutionVersionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
status

instance Prelude.NFData BatchInferenceJob where
  rnf :: BatchInferenceJob -> ()
rnf BatchInferenceJob' {Maybe Int
Maybe Text
Maybe POSIX
Maybe BatchInferenceJobConfig
Maybe BatchInferenceJobOutput
Maybe BatchInferenceJobInput
status :: Maybe Text
solutionVersionArn :: Maybe Text
roleArn :: Maybe Text
numResults :: Maybe Int
lastUpdatedDateTime :: Maybe POSIX
jobOutput :: Maybe BatchInferenceJobOutput
jobName :: Maybe Text
jobInput :: Maybe BatchInferenceJobInput
filterArn :: Maybe Text
failureReason :: Maybe Text
creationDateTime :: Maybe POSIX
batchInferenceJobConfig :: Maybe BatchInferenceJobConfig
batchInferenceJobArn :: Maybe Text
$sel:status:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:solutionVersionArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:roleArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:numResults:BatchInferenceJob' :: BatchInferenceJob -> Maybe Int
$sel:lastUpdatedDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
$sel:jobOutput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobOutput
$sel:jobName:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:jobInput:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobInput
$sel:filterArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:failureReason:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
$sel:creationDateTime:BatchInferenceJob' :: BatchInferenceJob -> Maybe POSIX
$sel:batchInferenceJobConfig:BatchInferenceJob' :: BatchInferenceJob -> Maybe BatchInferenceJobConfig
$sel:batchInferenceJobArn:BatchInferenceJob' :: BatchInferenceJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
batchInferenceJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BatchInferenceJobConfig
batchInferenceJobConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BatchInferenceJobInput
jobInput
      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 BatchInferenceJobOutput
jobOutput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numResults
      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 Text
solutionVersionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status