{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SageMaker.DescribeInferenceRecommendationsJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides the results of the Inference Recommender job. One or more
-- recommendation jobs are returned.
module Amazonka.SageMaker.DescribeInferenceRecommendationsJob
  ( -- * Creating a Request
    DescribeInferenceRecommendationsJob (..),
    newDescribeInferenceRecommendationsJob,

    -- * Request Lenses
    describeInferenceRecommendationsJob_jobName,

    -- * Destructuring the Response
    DescribeInferenceRecommendationsJobResponse (..),
    newDescribeInferenceRecommendationsJobResponse,

    -- * Response Lenses
    describeInferenceRecommendationsJobResponse_completionTime,
    describeInferenceRecommendationsJobResponse_endpointPerformances,
    describeInferenceRecommendationsJobResponse_failureReason,
    describeInferenceRecommendationsJobResponse_inferenceRecommendations,
    describeInferenceRecommendationsJobResponse_jobDescription,
    describeInferenceRecommendationsJobResponse_stoppingConditions,
    describeInferenceRecommendationsJobResponse_httpStatus,
    describeInferenceRecommendationsJobResponse_jobName,
    describeInferenceRecommendationsJobResponse_jobType,
    describeInferenceRecommendationsJobResponse_jobArn,
    describeInferenceRecommendationsJobResponse_roleArn,
    describeInferenceRecommendationsJobResponse_status,
    describeInferenceRecommendationsJobResponse_creationTime,
    describeInferenceRecommendationsJobResponse_lastModifiedTime,
    describeInferenceRecommendationsJobResponse_inputConfig,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMaker.Types

-- | /See:/ 'newDescribeInferenceRecommendationsJob' smart constructor.
data DescribeInferenceRecommendationsJob = DescribeInferenceRecommendationsJob'
  { -- | The name of the job. The name must be unique within an Amazon Web
    -- Services Region in the Amazon Web Services account.
    DescribeInferenceRecommendationsJob -> Text
jobName :: Prelude.Text
  }
  deriving (DescribeInferenceRecommendationsJob
-> DescribeInferenceRecommendationsJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInferenceRecommendationsJob
-> DescribeInferenceRecommendationsJob -> Bool
$c/= :: DescribeInferenceRecommendationsJob
-> DescribeInferenceRecommendationsJob -> Bool
== :: DescribeInferenceRecommendationsJob
-> DescribeInferenceRecommendationsJob -> Bool
$c== :: DescribeInferenceRecommendationsJob
-> DescribeInferenceRecommendationsJob -> Bool
Prelude.Eq, ReadPrec [DescribeInferenceRecommendationsJob]
ReadPrec DescribeInferenceRecommendationsJob
Int -> ReadS DescribeInferenceRecommendationsJob
ReadS [DescribeInferenceRecommendationsJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInferenceRecommendationsJob]
$creadListPrec :: ReadPrec [DescribeInferenceRecommendationsJob]
readPrec :: ReadPrec DescribeInferenceRecommendationsJob
$creadPrec :: ReadPrec DescribeInferenceRecommendationsJob
readList :: ReadS [DescribeInferenceRecommendationsJob]
$creadList :: ReadS [DescribeInferenceRecommendationsJob]
readsPrec :: Int -> ReadS DescribeInferenceRecommendationsJob
$creadsPrec :: Int -> ReadS DescribeInferenceRecommendationsJob
Prelude.Read, Int -> DescribeInferenceRecommendationsJob -> ShowS
[DescribeInferenceRecommendationsJob] -> ShowS
DescribeInferenceRecommendationsJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInferenceRecommendationsJob] -> ShowS
$cshowList :: [DescribeInferenceRecommendationsJob] -> ShowS
show :: DescribeInferenceRecommendationsJob -> String
$cshow :: DescribeInferenceRecommendationsJob -> String
showsPrec :: Int -> DescribeInferenceRecommendationsJob -> ShowS
$cshowsPrec :: Int -> DescribeInferenceRecommendationsJob -> ShowS
Prelude.Show, forall x.
Rep DescribeInferenceRecommendationsJob x
-> DescribeInferenceRecommendationsJob
forall x.
DescribeInferenceRecommendationsJob
-> Rep DescribeInferenceRecommendationsJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInferenceRecommendationsJob x
-> DescribeInferenceRecommendationsJob
$cfrom :: forall x.
DescribeInferenceRecommendationsJob
-> Rep DescribeInferenceRecommendationsJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInferenceRecommendationsJob' 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:
--
-- 'jobName', 'describeInferenceRecommendationsJob_jobName' - The name of the job. The name must be unique within an Amazon Web
-- Services Region in the Amazon Web Services account.
newDescribeInferenceRecommendationsJob ::
  -- | 'jobName'
  Prelude.Text ->
  DescribeInferenceRecommendationsJob
newDescribeInferenceRecommendationsJob :: Text -> DescribeInferenceRecommendationsJob
newDescribeInferenceRecommendationsJob Text
pJobName_ =
  DescribeInferenceRecommendationsJob'
    { $sel:jobName:DescribeInferenceRecommendationsJob' :: Text
jobName =
        Text
pJobName_
    }

-- | The name of the job. The name must be unique within an Amazon Web
-- Services Region in the Amazon Web Services account.
describeInferenceRecommendationsJob_jobName :: Lens.Lens' DescribeInferenceRecommendationsJob Prelude.Text
describeInferenceRecommendationsJob_jobName :: Lens' DescribeInferenceRecommendationsJob Text
describeInferenceRecommendationsJob_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJob' {Text
jobName :: Text
$sel:jobName:DescribeInferenceRecommendationsJob' :: DescribeInferenceRecommendationsJob -> Text
jobName} -> Text
jobName) (\s :: DescribeInferenceRecommendationsJob
s@DescribeInferenceRecommendationsJob' {} Text
a -> DescribeInferenceRecommendationsJob
s {$sel:jobName:DescribeInferenceRecommendationsJob' :: Text
jobName = Text
a} :: DescribeInferenceRecommendationsJob)

instance
  Core.AWSRequest
    DescribeInferenceRecommendationsJob
  where
  type
    AWSResponse DescribeInferenceRecommendationsJob =
      DescribeInferenceRecommendationsJobResponse
  request :: (Service -> Service)
-> DescribeInferenceRecommendationsJob
-> Request DescribeInferenceRecommendationsJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeInferenceRecommendationsJob
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeInferenceRecommendationsJob)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe POSIX
-> Maybe [EndpointPerformance]
-> Maybe Text
-> Maybe (NonEmpty InferenceRecommendation)
-> Maybe Text
-> Maybe RecommendationJobStoppingConditions
-> Int
-> Text
-> RecommendationJobType
-> Text
-> Text
-> RecommendationJobStatus
-> POSIX
-> POSIX
-> RecommendationJobInputConfig
-> DescribeInferenceRecommendationsJobResponse
DescribeInferenceRecommendationsJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CompletionTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndpointPerformances"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"InferenceRecommendations")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"JobDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StoppingConditions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 -> Either String 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 -> Either String a
Data..:> Key
"JobArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 -> Either String a
Data..:> Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"LastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"InputConfig")
      )

instance
  Prelude.Hashable
    DescribeInferenceRecommendationsJob
  where
  hashWithSalt :: Int -> DescribeInferenceRecommendationsJob -> Int
hashWithSalt
    Int
_salt
    DescribeInferenceRecommendationsJob' {Text
jobName :: Text
$sel:jobName:DescribeInferenceRecommendationsJob' :: DescribeInferenceRecommendationsJob -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobName

instance
  Prelude.NFData
    DescribeInferenceRecommendationsJob
  where
  rnf :: DescribeInferenceRecommendationsJob -> ()
rnf DescribeInferenceRecommendationsJob' {Text
jobName :: Text
$sel:jobName:DescribeInferenceRecommendationsJob' :: DescribeInferenceRecommendationsJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
jobName

instance
  Data.ToHeaders
    DescribeInferenceRecommendationsJob
  where
  toHeaders :: DescribeInferenceRecommendationsJob -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"SageMaker.DescribeInferenceRecommendationsJob" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    DescribeInferenceRecommendationsJob
  where
  toJSON :: DescribeInferenceRecommendationsJob -> Value
toJSON DescribeInferenceRecommendationsJob' {Text
jobName :: Text
$sel:jobName:DescribeInferenceRecommendationsJob' :: DescribeInferenceRecommendationsJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"JobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobName)]
      )

instance
  Data.ToPath
    DescribeInferenceRecommendationsJob
  where
  toPath :: DescribeInferenceRecommendationsJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance
  Data.ToQuery
    DescribeInferenceRecommendationsJob
  where
  toQuery :: DescribeInferenceRecommendationsJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeInferenceRecommendationsJobResponse' smart constructor.
data DescribeInferenceRecommendationsJobResponse = DescribeInferenceRecommendationsJobResponse'
  { -- | A timestamp that shows when the job completed.
    DescribeInferenceRecommendationsJobResponse -> Maybe POSIX
completionTime :: Prelude.Maybe Data.POSIX,
    -- | The performance results from running an Inference Recommender job on an
    -- existing endpoint.
    DescribeInferenceRecommendationsJobResponse
-> Maybe [EndpointPerformance]
endpointPerformances :: Prelude.Maybe [EndpointPerformance],
    -- | If the job fails, provides information why the job failed.
    DescribeInferenceRecommendationsJobResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The recommendations made by Inference Recommender.
    DescribeInferenceRecommendationsJobResponse
-> Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations :: Prelude.Maybe (Prelude.NonEmpty InferenceRecommendation),
    -- | The job description that you provided when you initiated the job.
    DescribeInferenceRecommendationsJobResponse -> Maybe Text
jobDescription :: Prelude.Maybe Prelude.Text,
    -- | The stopping conditions that you provided when you initiated the job.
    DescribeInferenceRecommendationsJobResponse
-> Maybe RecommendationJobStoppingConditions
stoppingConditions :: Prelude.Maybe RecommendationJobStoppingConditions,
    -- | The response's http status code.
    DescribeInferenceRecommendationsJobResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the job. The name must be unique within an Amazon Web
    -- Services Region in the Amazon Web Services account.
    DescribeInferenceRecommendationsJobResponse -> Text
jobName :: Prelude.Text,
    -- | The job type that you provided when you initiated the job.
    DescribeInferenceRecommendationsJobResponse
-> RecommendationJobType
jobType :: RecommendationJobType,
    -- | The Amazon Resource Name (ARN) of the job.
    DescribeInferenceRecommendationsJobResponse -> Text
jobArn :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
    -- Access Management (IAM) role you provided when you initiated the job.
    DescribeInferenceRecommendationsJobResponse -> Text
roleArn :: Prelude.Text,
    -- | The status of the job.
    DescribeInferenceRecommendationsJobResponse
-> RecommendationJobStatus
status :: RecommendationJobStatus,
    -- | A timestamp that shows when the job was created.
    DescribeInferenceRecommendationsJobResponse -> POSIX
creationTime :: Data.POSIX,
    -- | A timestamp that shows when the job was last modified.
    DescribeInferenceRecommendationsJobResponse -> POSIX
lastModifiedTime :: Data.POSIX,
    -- | Returns information about the versioned model package Amazon Resource
    -- Name (ARN), the traffic pattern, and endpoint configurations you
    -- provided when you initiated the job.
    DescribeInferenceRecommendationsJobResponse
-> RecommendationJobInputConfig
inputConfig :: RecommendationJobInputConfig
  }
  deriving (DescribeInferenceRecommendationsJobResponse
-> DescribeInferenceRecommendationsJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInferenceRecommendationsJobResponse
-> DescribeInferenceRecommendationsJobResponse -> Bool
$c/= :: DescribeInferenceRecommendationsJobResponse
-> DescribeInferenceRecommendationsJobResponse -> Bool
== :: DescribeInferenceRecommendationsJobResponse
-> DescribeInferenceRecommendationsJobResponse -> Bool
$c== :: DescribeInferenceRecommendationsJobResponse
-> DescribeInferenceRecommendationsJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeInferenceRecommendationsJobResponse]
ReadPrec DescribeInferenceRecommendationsJobResponse
Int -> ReadS DescribeInferenceRecommendationsJobResponse
ReadS [DescribeInferenceRecommendationsJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInferenceRecommendationsJobResponse]
$creadListPrec :: ReadPrec [DescribeInferenceRecommendationsJobResponse]
readPrec :: ReadPrec DescribeInferenceRecommendationsJobResponse
$creadPrec :: ReadPrec DescribeInferenceRecommendationsJobResponse
readList :: ReadS [DescribeInferenceRecommendationsJobResponse]
$creadList :: ReadS [DescribeInferenceRecommendationsJobResponse]
readsPrec :: Int -> ReadS DescribeInferenceRecommendationsJobResponse
$creadsPrec :: Int -> ReadS DescribeInferenceRecommendationsJobResponse
Prelude.Read, Int -> DescribeInferenceRecommendationsJobResponse -> ShowS
[DescribeInferenceRecommendationsJobResponse] -> ShowS
DescribeInferenceRecommendationsJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInferenceRecommendationsJobResponse] -> ShowS
$cshowList :: [DescribeInferenceRecommendationsJobResponse] -> ShowS
show :: DescribeInferenceRecommendationsJobResponse -> String
$cshow :: DescribeInferenceRecommendationsJobResponse -> String
showsPrec :: Int -> DescribeInferenceRecommendationsJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeInferenceRecommendationsJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeInferenceRecommendationsJobResponse x
-> DescribeInferenceRecommendationsJobResponse
forall x.
DescribeInferenceRecommendationsJobResponse
-> Rep DescribeInferenceRecommendationsJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInferenceRecommendationsJobResponse x
-> DescribeInferenceRecommendationsJobResponse
$cfrom :: forall x.
DescribeInferenceRecommendationsJobResponse
-> Rep DescribeInferenceRecommendationsJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInferenceRecommendationsJobResponse' 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:
--
-- 'completionTime', 'describeInferenceRecommendationsJobResponse_completionTime' - A timestamp that shows when the job completed.
--
-- 'endpointPerformances', 'describeInferenceRecommendationsJobResponse_endpointPerformances' - The performance results from running an Inference Recommender job on an
-- existing endpoint.
--
-- 'failureReason', 'describeInferenceRecommendationsJobResponse_failureReason' - If the job fails, provides information why the job failed.
--
-- 'inferenceRecommendations', 'describeInferenceRecommendationsJobResponse_inferenceRecommendations' - The recommendations made by Inference Recommender.
--
-- 'jobDescription', 'describeInferenceRecommendationsJobResponse_jobDescription' - The job description that you provided when you initiated the job.
--
-- 'stoppingConditions', 'describeInferenceRecommendationsJobResponse_stoppingConditions' - The stopping conditions that you provided when you initiated the job.
--
-- 'httpStatus', 'describeInferenceRecommendationsJobResponse_httpStatus' - The response's http status code.
--
-- 'jobName', 'describeInferenceRecommendationsJobResponse_jobName' - The name of the job. The name must be unique within an Amazon Web
-- Services Region in the Amazon Web Services account.
--
-- 'jobType', 'describeInferenceRecommendationsJobResponse_jobType' - The job type that you provided when you initiated the job.
--
-- 'jobArn', 'describeInferenceRecommendationsJobResponse_jobArn' - The Amazon Resource Name (ARN) of the job.
--
-- 'roleArn', 'describeInferenceRecommendationsJobResponse_roleArn' - The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
-- Access Management (IAM) role you provided when you initiated the job.
--
-- 'status', 'describeInferenceRecommendationsJobResponse_status' - The status of the job.
--
-- 'creationTime', 'describeInferenceRecommendationsJobResponse_creationTime' - A timestamp that shows when the job was created.
--
-- 'lastModifiedTime', 'describeInferenceRecommendationsJobResponse_lastModifiedTime' - A timestamp that shows when the job was last modified.
--
-- 'inputConfig', 'describeInferenceRecommendationsJobResponse_inputConfig' - Returns information about the versioned model package Amazon Resource
-- Name (ARN), the traffic pattern, and endpoint configurations you
-- provided when you initiated the job.
newDescribeInferenceRecommendationsJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'jobName'
  Prelude.Text ->
  -- | 'jobType'
  RecommendationJobType ->
  -- | 'jobArn'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  -- | 'status'
  RecommendationJobStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  -- | 'inputConfig'
  RecommendationJobInputConfig ->
  DescribeInferenceRecommendationsJobResponse
newDescribeInferenceRecommendationsJobResponse :: Int
-> Text
-> RecommendationJobType
-> Text
-> Text
-> RecommendationJobStatus
-> UTCTime
-> UTCTime
-> RecommendationJobInputConfig
-> DescribeInferenceRecommendationsJobResponse
newDescribeInferenceRecommendationsJobResponse
  Int
pHttpStatus_
  Text
pJobName_
  RecommendationJobType
pJobType_
  Text
pJobArn_
  Text
pRoleArn_
  RecommendationJobStatus
pStatus_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_
  RecommendationJobInputConfig
pInputConfig_ =
    DescribeInferenceRecommendationsJobResponse'
      { $sel:completionTime:DescribeInferenceRecommendationsJobResponse' :: Maybe POSIX
completionTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:endpointPerformances:DescribeInferenceRecommendationsJobResponse' :: Maybe [EndpointPerformance]
endpointPerformances =
          forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:DescribeInferenceRecommendationsJobResponse' :: Maybe Text
failureReason =
          forall a. Maybe a
Prelude.Nothing,
        $sel:inferenceRecommendations:DescribeInferenceRecommendationsJobResponse' :: Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:jobDescription:DescribeInferenceRecommendationsJobResponse' :: Maybe Text
jobDescription =
          forall a. Maybe a
Prelude.Nothing,
        $sel:stoppingConditions:DescribeInferenceRecommendationsJobResponse' :: Maybe RecommendationJobStoppingConditions
stoppingConditions =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeInferenceRecommendationsJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:jobName:DescribeInferenceRecommendationsJobResponse' :: Text
jobName = Text
pJobName_,
        $sel:jobType:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobType
jobType = RecommendationJobType
pJobType_,
        $sel:jobArn:DescribeInferenceRecommendationsJobResponse' :: Text
jobArn = Text
pJobArn_,
        $sel:roleArn:DescribeInferenceRecommendationsJobResponse' :: Text
roleArn = Text
pRoleArn_,
        $sel:status:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobStatus
status = RecommendationJobStatus
pStatus_,
        $sel:creationTime:DescribeInferenceRecommendationsJobResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
            forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:DescribeInferenceRecommendationsJobResponse' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
            forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_,
        $sel:inputConfig:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobInputConfig
inputConfig = RecommendationJobInputConfig
pInputConfig_
      }

-- | A timestamp that shows when the job completed.
describeInferenceRecommendationsJobResponse_completionTime :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe Prelude.UTCTime)
describeInferenceRecommendationsJobResponse_completionTime :: Lens' DescribeInferenceRecommendationsJobResponse (Maybe UTCTime)
describeInferenceRecommendationsJobResponse_completionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe POSIX
completionTime :: Maybe POSIX
$sel:completionTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe POSIX
completionTime} -> Maybe POSIX
completionTime) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe POSIX
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:completionTime:DescribeInferenceRecommendationsJobResponse' :: Maybe POSIX
completionTime = Maybe POSIX
a} :: DescribeInferenceRecommendationsJobResponse) 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 performance results from running an Inference Recommender job on an
-- existing endpoint.
describeInferenceRecommendationsJobResponse_endpointPerformances :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe [EndpointPerformance])
describeInferenceRecommendationsJobResponse_endpointPerformances :: Lens'
  DescribeInferenceRecommendationsJobResponse
  (Maybe [EndpointPerformance])
describeInferenceRecommendationsJobResponse_endpointPerformances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe [EndpointPerformance]
endpointPerformances :: Maybe [EndpointPerformance]
$sel:endpointPerformances:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe [EndpointPerformance]
endpointPerformances} -> Maybe [EndpointPerformance]
endpointPerformances) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe [EndpointPerformance]
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:endpointPerformances:DescribeInferenceRecommendationsJobResponse' :: Maybe [EndpointPerformance]
endpointPerformances = Maybe [EndpointPerformance]
a} :: DescribeInferenceRecommendationsJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | If the job fails, provides information why the job failed.
describeInferenceRecommendationsJobResponse_failureReason :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe Prelude.Text)
describeInferenceRecommendationsJobResponse_failureReason :: Lens' DescribeInferenceRecommendationsJobResponse (Maybe Text)
describeInferenceRecommendationsJobResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe Text
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:failureReason:DescribeInferenceRecommendationsJobResponse' :: Maybe Text
failureReason = Maybe Text
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The recommendations made by Inference Recommender.
describeInferenceRecommendationsJobResponse_inferenceRecommendations :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe (Prelude.NonEmpty InferenceRecommendation))
describeInferenceRecommendationsJobResponse_inferenceRecommendations :: Lens'
  DescribeInferenceRecommendationsJobResponse
  (Maybe (NonEmpty InferenceRecommendation))
describeInferenceRecommendationsJobResponse_inferenceRecommendations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations :: Maybe (NonEmpty InferenceRecommendation)
$sel:inferenceRecommendations:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations} -> Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe (NonEmpty InferenceRecommendation)
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:inferenceRecommendations:DescribeInferenceRecommendationsJobResponse' :: Maybe (NonEmpty InferenceRecommendation)
inferenceRecommendations = Maybe (NonEmpty InferenceRecommendation)
a} :: DescribeInferenceRecommendationsJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The job description that you provided when you initiated the job.
describeInferenceRecommendationsJobResponse_jobDescription :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe Prelude.Text)
describeInferenceRecommendationsJobResponse_jobDescription :: Lens' DescribeInferenceRecommendationsJobResponse (Maybe Text)
describeInferenceRecommendationsJobResponse_jobDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe Text
jobDescription :: Maybe Text
$sel:jobDescription:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe Text
jobDescription} -> Maybe Text
jobDescription) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe Text
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:jobDescription:DescribeInferenceRecommendationsJobResponse' :: Maybe Text
jobDescription = Maybe Text
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The stopping conditions that you provided when you initiated the job.
describeInferenceRecommendationsJobResponse_stoppingConditions :: Lens.Lens' DescribeInferenceRecommendationsJobResponse (Prelude.Maybe RecommendationJobStoppingConditions)
describeInferenceRecommendationsJobResponse_stoppingConditions :: Lens'
  DescribeInferenceRecommendationsJobResponse
  (Maybe RecommendationJobStoppingConditions)
describeInferenceRecommendationsJobResponse_stoppingConditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Maybe RecommendationJobStoppingConditions
stoppingConditions :: Maybe RecommendationJobStoppingConditions
$sel:stoppingConditions:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe RecommendationJobStoppingConditions
stoppingConditions} -> Maybe RecommendationJobStoppingConditions
stoppingConditions) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Maybe RecommendationJobStoppingConditions
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:stoppingConditions:DescribeInferenceRecommendationsJobResponse' :: Maybe RecommendationJobStoppingConditions
stoppingConditions = Maybe RecommendationJobStoppingConditions
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The response's http status code.
describeInferenceRecommendationsJobResponse_httpStatus :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.Int
describeInferenceRecommendationsJobResponse_httpStatus :: Lens' DescribeInferenceRecommendationsJobResponse Int
describeInferenceRecommendationsJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Int
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:httpStatus:DescribeInferenceRecommendationsJobResponse' :: Int
httpStatus = Int
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The name of the job. The name must be unique within an Amazon Web
-- Services Region in the Amazon Web Services account.
describeInferenceRecommendationsJobResponse_jobName :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.Text
describeInferenceRecommendationsJobResponse_jobName :: Lens' DescribeInferenceRecommendationsJobResponse Text
describeInferenceRecommendationsJobResponse_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Text
jobName :: Text
$sel:jobName:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
jobName} -> Text
jobName) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Text
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:jobName:DescribeInferenceRecommendationsJobResponse' :: Text
jobName = Text
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The job type that you provided when you initiated the job.
describeInferenceRecommendationsJobResponse_jobType :: Lens.Lens' DescribeInferenceRecommendationsJobResponse RecommendationJobType
describeInferenceRecommendationsJobResponse_jobType :: Lens'
  DescribeInferenceRecommendationsJobResponse RecommendationJobType
describeInferenceRecommendationsJobResponse_jobType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {RecommendationJobType
jobType :: RecommendationJobType
$sel:jobType:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobType
jobType} -> RecommendationJobType
jobType) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} RecommendationJobType
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:jobType:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobType
jobType = RecommendationJobType
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The Amazon Resource Name (ARN) of the job.
describeInferenceRecommendationsJobResponse_jobArn :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.Text
describeInferenceRecommendationsJobResponse_jobArn :: Lens' DescribeInferenceRecommendationsJobResponse Text
describeInferenceRecommendationsJobResponse_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Text
jobArn :: Text
$sel:jobArn:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
jobArn} -> Text
jobArn) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Text
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:jobArn:DescribeInferenceRecommendationsJobResponse' :: Text
jobArn = Text
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
-- Access Management (IAM) role you provided when you initiated the job.
describeInferenceRecommendationsJobResponse_roleArn :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.Text
describeInferenceRecommendationsJobResponse_roleArn :: Lens' DescribeInferenceRecommendationsJobResponse Text
describeInferenceRecommendationsJobResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {Text
roleArn :: Text
$sel:roleArn:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
roleArn} -> Text
roleArn) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} Text
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:roleArn:DescribeInferenceRecommendationsJobResponse' :: Text
roleArn = Text
a} :: DescribeInferenceRecommendationsJobResponse)

-- | The status of the job.
describeInferenceRecommendationsJobResponse_status :: Lens.Lens' DescribeInferenceRecommendationsJobResponse RecommendationJobStatus
describeInferenceRecommendationsJobResponse_status :: Lens'
  DescribeInferenceRecommendationsJobResponse RecommendationJobStatus
describeInferenceRecommendationsJobResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {RecommendationJobStatus
status :: RecommendationJobStatus
$sel:status:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobStatus
status} -> RecommendationJobStatus
status) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} RecommendationJobStatus
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:status:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobStatus
status = RecommendationJobStatus
a} :: DescribeInferenceRecommendationsJobResponse)

-- | A timestamp that shows when the job was created.
describeInferenceRecommendationsJobResponse_creationTime :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.UTCTime
describeInferenceRecommendationsJobResponse_creationTime :: Lens' DescribeInferenceRecommendationsJobResponse UTCTime
describeInferenceRecommendationsJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} POSIX
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:creationTime:DescribeInferenceRecommendationsJobResponse' :: POSIX
creationTime = POSIX
a} :: DescribeInferenceRecommendationsJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A timestamp that shows when the job was last modified.
describeInferenceRecommendationsJobResponse_lastModifiedTime :: Lens.Lens' DescribeInferenceRecommendationsJobResponse Prelude.UTCTime
describeInferenceRecommendationsJobResponse_lastModifiedTime :: Lens' DescribeInferenceRecommendationsJobResponse UTCTime
describeInferenceRecommendationsJobResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} POSIX
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:lastModifiedTime:DescribeInferenceRecommendationsJobResponse' :: POSIX
lastModifiedTime = POSIX
a} :: DescribeInferenceRecommendationsJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Returns information about the versioned model package Amazon Resource
-- Name (ARN), the traffic pattern, and endpoint configurations you
-- provided when you initiated the job.
describeInferenceRecommendationsJobResponse_inputConfig :: Lens.Lens' DescribeInferenceRecommendationsJobResponse RecommendationJobInputConfig
describeInferenceRecommendationsJobResponse_inputConfig :: Lens'
  DescribeInferenceRecommendationsJobResponse
  RecommendationJobInputConfig
describeInferenceRecommendationsJobResponse_inputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInferenceRecommendationsJobResponse' {RecommendationJobInputConfig
inputConfig :: RecommendationJobInputConfig
$sel:inputConfig:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobInputConfig
inputConfig} -> RecommendationJobInputConfig
inputConfig) (\s :: DescribeInferenceRecommendationsJobResponse
s@DescribeInferenceRecommendationsJobResponse' {} RecommendationJobInputConfig
a -> DescribeInferenceRecommendationsJobResponse
s {$sel:inputConfig:DescribeInferenceRecommendationsJobResponse' :: RecommendationJobInputConfig
inputConfig = RecommendationJobInputConfig
a} :: DescribeInferenceRecommendationsJobResponse)

instance
  Prelude.NFData
    DescribeInferenceRecommendationsJobResponse
  where
  rnf :: DescribeInferenceRecommendationsJobResponse -> ()
rnf DescribeInferenceRecommendationsJobResponse' {Int
Maybe [EndpointPerformance]
Maybe (NonEmpty InferenceRecommendation)
Maybe Text
Maybe POSIX
Maybe RecommendationJobStoppingConditions
Text
POSIX
RecommendationJobStatus
RecommendationJobType
RecommendationJobInputConfig
inputConfig :: RecommendationJobInputConfig
lastModifiedTime :: POSIX
creationTime :: POSIX
status :: RecommendationJobStatus
roleArn :: Text
jobArn :: Text
jobType :: RecommendationJobType
jobName :: Text
httpStatus :: Int
stoppingConditions :: Maybe RecommendationJobStoppingConditions
jobDescription :: Maybe Text
inferenceRecommendations :: Maybe (NonEmpty InferenceRecommendation)
failureReason :: Maybe Text
endpointPerformances :: Maybe [EndpointPerformance]
completionTime :: Maybe POSIX
$sel:inputConfig:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobInputConfig
$sel:lastModifiedTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> POSIX
$sel:creationTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> POSIX
$sel:status:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobStatus
$sel:roleArn:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
$sel:jobArn:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
$sel:jobType:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> RecommendationJobType
$sel:jobName:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Text
$sel:httpStatus:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Int
$sel:stoppingConditions:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe RecommendationJobStoppingConditions
$sel:jobDescription:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe Text
$sel:inferenceRecommendations:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe (NonEmpty InferenceRecommendation)
$sel:failureReason:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe Text
$sel:endpointPerformances:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse
-> Maybe [EndpointPerformance]
$sel:completionTime:DescribeInferenceRecommendationsJobResponse' :: DescribeInferenceRecommendationsJobResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [EndpointPerformance]
endpointPerformances
      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 (NonEmpty InferenceRecommendation)
inferenceRecommendations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecommendationJobStoppingConditions
stoppingConditions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RecommendationJobType
jobType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RecommendationJobStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RecommendationJobInputConfig
inputConfig