{-# 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.MachineLearning.GetEvaluation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns an @Evaluation@ that includes metadata as well as the current
-- status of the @Evaluation@.
module Amazonka.MachineLearning.GetEvaluation
  ( -- * Creating a Request
    GetEvaluation (..),
    newGetEvaluation,

    -- * Request Lenses
    getEvaluation_evaluationId,

    -- * Destructuring the Response
    GetEvaluationResponse (..),
    newGetEvaluationResponse,

    -- * Response Lenses
    getEvaluationResponse_computeTime,
    getEvaluationResponse_createdAt,
    getEvaluationResponse_createdByIamUser,
    getEvaluationResponse_evaluationDataSourceId,
    getEvaluationResponse_evaluationId,
    getEvaluationResponse_finishedAt,
    getEvaluationResponse_inputDataLocationS3,
    getEvaluationResponse_lastUpdatedAt,
    getEvaluationResponse_logUri,
    getEvaluationResponse_mLModelId,
    getEvaluationResponse_message,
    getEvaluationResponse_name,
    getEvaluationResponse_performanceMetrics,
    getEvaluationResponse_startedAt,
    getEvaluationResponse_status,
    getEvaluationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MachineLearning.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetEvaluation' smart constructor.
data GetEvaluation = GetEvaluation'
  { -- | The ID of the @Evaluation@ to retrieve. The evaluation of each @MLModel@
    -- is recorded and cataloged. The ID provides the means to access the
    -- information.
    GetEvaluation -> Text
evaluationId :: Prelude.Text
  }
  deriving (GetEvaluation -> GetEvaluation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEvaluation -> GetEvaluation -> Bool
$c/= :: GetEvaluation -> GetEvaluation -> Bool
== :: GetEvaluation -> GetEvaluation -> Bool
$c== :: GetEvaluation -> GetEvaluation -> Bool
Prelude.Eq, ReadPrec [GetEvaluation]
ReadPrec GetEvaluation
Int -> ReadS GetEvaluation
ReadS [GetEvaluation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEvaluation]
$creadListPrec :: ReadPrec [GetEvaluation]
readPrec :: ReadPrec GetEvaluation
$creadPrec :: ReadPrec GetEvaluation
readList :: ReadS [GetEvaluation]
$creadList :: ReadS [GetEvaluation]
readsPrec :: Int -> ReadS GetEvaluation
$creadsPrec :: Int -> ReadS GetEvaluation
Prelude.Read, Int -> GetEvaluation -> ShowS
[GetEvaluation] -> ShowS
GetEvaluation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEvaluation] -> ShowS
$cshowList :: [GetEvaluation] -> ShowS
show :: GetEvaluation -> String
$cshow :: GetEvaluation -> String
showsPrec :: Int -> GetEvaluation -> ShowS
$cshowsPrec :: Int -> GetEvaluation -> ShowS
Prelude.Show, forall x. Rep GetEvaluation x -> GetEvaluation
forall x. GetEvaluation -> Rep GetEvaluation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEvaluation x -> GetEvaluation
$cfrom :: forall x. GetEvaluation -> Rep GetEvaluation x
Prelude.Generic)

-- |
-- Create a value of 'GetEvaluation' 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:
--
-- 'evaluationId', 'getEvaluation_evaluationId' - The ID of the @Evaluation@ to retrieve. The evaluation of each @MLModel@
-- is recorded and cataloged. The ID provides the means to access the
-- information.
newGetEvaluation ::
  -- | 'evaluationId'
  Prelude.Text ->
  GetEvaluation
newGetEvaluation :: Text -> GetEvaluation
newGetEvaluation Text
pEvaluationId_ =
  GetEvaluation' {$sel:evaluationId:GetEvaluation' :: Text
evaluationId = Text
pEvaluationId_}

-- | The ID of the @Evaluation@ to retrieve. The evaluation of each @MLModel@
-- is recorded and cataloged. The ID provides the means to access the
-- information.
getEvaluation_evaluationId :: Lens.Lens' GetEvaluation Prelude.Text
getEvaluation_evaluationId :: Lens' GetEvaluation Text
getEvaluation_evaluationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluation' {Text
evaluationId :: Text
$sel:evaluationId:GetEvaluation' :: GetEvaluation -> Text
evaluationId} -> Text
evaluationId) (\s :: GetEvaluation
s@GetEvaluation' {} Text
a -> GetEvaluation
s {$sel:evaluationId:GetEvaluation' :: Text
evaluationId = Text
a} :: GetEvaluation)

instance Core.AWSRequest GetEvaluation where
  type
    AWSResponse GetEvaluation =
      GetEvaluationResponse
  request :: (Service -> Service) -> GetEvaluation -> Request GetEvaluation
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 GetEvaluation
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetEvaluation)))
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 Integer
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PerformanceMetrics
-> Maybe POSIX
-> Maybe EntityStatus
-> Int
-> GetEvaluationResponse
GetEvaluationResponse'
            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
"ComputeTime")
            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
"CreatedAt")
            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
"CreatedByIamUser")
            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
"EvaluationDataSourceId")
            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
"EvaluationId")
            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
"FinishedAt")
            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
"InputDataLocationS3")
            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
"LastUpdatedAt")
            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
"LogUri")
            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
"MLModelId")
            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
"Message")
            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
"Name")
            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
"PerformanceMetrics")
            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
"StartedAt")
            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
"Status")
            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))
      )

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

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

instance Data.ToHeaders GetEvaluation where
  toHeaders :: GetEvaluation -> 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
"AmazonML_20141212.GetEvaluation" ::
                          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 GetEvaluation where
  toJSON :: GetEvaluation -> Value
toJSON GetEvaluation' {Text
evaluationId :: Text
$sel:evaluationId:GetEvaluation' :: GetEvaluation -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"EvaluationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
evaluationId)]
      )

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

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

-- | Represents the output of a @GetEvaluation@ operation and describes an
-- @Evaluation@.
--
-- /See:/ 'newGetEvaluationResponse' smart constructor.
data GetEvaluationResponse = GetEvaluationResponse'
  { -- | The approximate CPU time in milliseconds that Amazon Machine Learning
    -- spent processing the @Evaluation@, normalized and scaled on computation
    -- resources. @ComputeTime@ is only available if the @Evaluation@ is in the
    -- @COMPLETED@ state.
    GetEvaluationResponse -> Maybe Integer
computeTime :: Prelude.Maybe Prelude.Integer,
    -- | The time that the @Evaluation@ was created. The time is expressed in
    -- epoch time.
    GetEvaluationResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The AWS user account that invoked the evaluation. The account type can
    -- be either an AWS root account or an AWS Identity and Access Management
    -- (IAM) user account.
    GetEvaluationResponse -> Maybe Text
createdByIamUser :: Prelude.Maybe Prelude.Text,
    -- | The @DataSource@ used for this evaluation.
    GetEvaluationResponse -> Maybe Text
evaluationDataSourceId :: Prelude.Maybe Prelude.Text,
    -- | The evaluation ID which is same as the @EvaluationId@ in the request.
    GetEvaluationResponse -> Maybe Text
evaluationId :: Prelude.Maybe Prelude.Text,
    -- | The epoch time when Amazon Machine Learning marked the @Evaluation@ as
    -- @COMPLETED@ or @FAILED@. @FinishedAt@ is only available when the
    -- @Evaluation@ is in the @COMPLETED@ or @FAILED@ state.
    GetEvaluationResponse -> Maybe POSIX
finishedAt :: Prelude.Maybe Data.POSIX,
    -- | The location of the data file or directory in Amazon Simple Storage
    -- Service (Amazon S3).
    GetEvaluationResponse -> Maybe Text
inputDataLocationS3 :: Prelude.Maybe Prelude.Text,
    -- | The time of the most recent edit to the @Evaluation@. The time is
    -- expressed in epoch time.
    GetEvaluationResponse -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | A link to the file that contains logs of the @CreateEvaluation@
    -- operation.
    GetEvaluationResponse -> Maybe Text
logUri :: Prelude.Maybe Prelude.Text,
    -- | The ID of the @MLModel@ that was the focus of the evaluation.
    GetEvaluationResponse -> Maybe Text
mLModelId :: Prelude.Maybe Prelude.Text,
    -- | A description of the most recent details about evaluating the @MLModel@.
    GetEvaluationResponse -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | A user-supplied name or description of the @Evaluation@.
    GetEvaluationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Measurements of how well the @MLModel@ performed using observations
    -- referenced by the @DataSource@. One of the following metric is returned
    -- based on the type of the @MLModel@:
    --
    -- -   BinaryAUC: A binary @MLModel@ uses the Area Under the Curve (AUC)
    --     technique to measure performance.
    --
    -- -   RegressionRMSE: A regression @MLModel@ uses the Root Mean Square
    --     Error (RMSE) technique to measure performance. RMSE measures the
    --     difference between predicted and actual values for a single
    --     variable.
    --
    -- -   MulticlassAvgFScore: A multiclass @MLModel@ uses the F1 score
    --     technique to measure performance.
    --
    -- For more information about performance metrics, please see the
    -- <https://docs.aws.amazon.com/machine-learning/latest/dg Amazon Machine Learning Developer Guide>.
    GetEvaluationResponse -> Maybe PerformanceMetrics
performanceMetrics :: Prelude.Maybe PerformanceMetrics,
    -- | The epoch time when Amazon Machine Learning marked the @Evaluation@ as
    -- @INPROGRESS@. @StartedAt@ isn\'t available if the @Evaluation@ is in the
    -- @PENDING@ state.
    GetEvaluationResponse -> Maybe POSIX
startedAt :: Prelude.Maybe Data.POSIX,
    -- | The status of the evaluation. This element can have one of the following
    -- values:
    --
    -- -   @PENDING@ - Amazon Machine Language (Amazon ML) submitted a request
    --     to evaluate an @MLModel@.
    --
    -- -   @INPROGRESS@ - The evaluation is underway.
    --
    -- -   @FAILED@ - The request to evaluate an @MLModel@ did not run to
    --     completion. It is not usable.
    --
    -- -   @COMPLETED@ - The evaluation process completed successfully.
    --
    -- -   @DELETED@ - The @Evaluation@ is marked as deleted. It is not usable.
    GetEvaluationResponse -> Maybe EntityStatus
status :: Prelude.Maybe EntityStatus,
    -- | The response's http status code.
    GetEvaluationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetEvaluationResponse -> GetEvaluationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEvaluationResponse -> GetEvaluationResponse -> Bool
$c/= :: GetEvaluationResponse -> GetEvaluationResponse -> Bool
== :: GetEvaluationResponse -> GetEvaluationResponse -> Bool
$c== :: GetEvaluationResponse -> GetEvaluationResponse -> Bool
Prelude.Eq, ReadPrec [GetEvaluationResponse]
ReadPrec GetEvaluationResponse
Int -> ReadS GetEvaluationResponse
ReadS [GetEvaluationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEvaluationResponse]
$creadListPrec :: ReadPrec [GetEvaluationResponse]
readPrec :: ReadPrec GetEvaluationResponse
$creadPrec :: ReadPrec GetEvaluationResponse
readList :: ReadS [GetEvaluationResponse]
$creadList :: ReadS [GetEvaluationResponse]
readsPrec :: Int -> ReadS GetEvaluationResponse
$creadsPrec :: Int -> ReadS GetEvaluationResponse
Prelude.Read, Int -> GetEvaluationResponse -> ShowS
[GetEvaluationResponse] -> ShowS
GetEvaluationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEvaluationResponse] -> ShowS
$cshowList :: [GetEvaluationResponse] -> ShowS
show :: GetEvaluationResponse -> String
$cshow :: GetEvaluationResponse -> String
showsPrec :: Int -> GetEvaluationResponse -> ShowS
$cshowsPrec :: Int -> GetEvaluationResponse -> ShowS
Prelude.Show, forall x. Rep GetEvaluationResponse x -> GetEvaluationResponse
forall x. GetEvaluationResponse -> Rep GetEvaluationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEvaluationResponse x -> GetEvaluationResponse
$cfrom :: forall x. GetEvaluationResponse -> Rep GetEvaluationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetEvaluationResponse' 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:
--
-- 'computeTime', 'getEvaluationResponse_computeTime' - The approximate CPU time in milliseconds that Amazon Machine Learning
-- spent processing the @Evaluation@, normalized and scaled on computation
-- resources. @ComputeTime@ is only available if the @Evaluation@ is in the
-- @COMPLETED@ state.
--
-- 'createdAt', 'getEvaluationResponse_createdAt' - The time that the @Evaluation@ was created. The time is expressed in
-- epoch time.
--
-- 'createdByIamUser', 'getEvaluationResponse_createdByIamUser' - The AWS user account that invoked the evaluation. The account type can
-- be either an AWS root account or an AWS Identity and Access Management
-- (IAM) user account.
--
-- 'evaluationDataSourceId', 'getEvaluationResponse_evaluationDataSourceId' - The @DataSource@ used for this evaluation.
--
-- 'evaluationId', 'getEvaluationResponse_evaluationId' - The evaluation ID which is same as the @EvaluationId@ in the request.
--
-- 'finishedAt', 'getEvaluationResponse_finishedAt' - The epoch time when Amazon Machine Learning marked the @Evaluation@ as
-- @COMPLETED@ or @FAILED@. @FinishedAt@ is only available when the
-- @Evaluation@ is in the @COMPLETED@ or @FAILED@ state.
--
-- 'inputDataLocationS3', 'getEvaluationResponse_inputDataLocationS3' - The location of the data file or directory in Amazon Simple Storage
-- Service (Amazon S3).
--
-- 'lastUpdatedAt', 'getEvaluationResponse_lastUpdatedAt' - The time of the most recent edit to the @Evaluation@. The time is
-- expressed in epoch time.
--
-- 'logUri', 'getEvaluationResponse_logUri' - A link to the file that contains logs of the @CreateEvaluation@
-- operation.
--
-- 'mLModelId', 'getEvaluationResponse_mLModelId' - The ID of the @MLModel@ that was the focus of the evaluation.
--
-- 'message', 'getEvaluationResponse_message' - A description of the most recent details about evaluating the @MLModel@.
--
-- 'name', 'getEvaluationResponse_name' - A user-supplied name or description of the @Evaluation@.
--
-- 'performanceMetrics', 'getEvaluationResponse_performanceMetrics' - Measurements of how well the @MLModel@ performed using observations
-- referenced by the @DataSource@. One of the following metric is returned
-- based on the type of the @MLModel@:
--
-- -   BinaryAUC: A binary @MLModel@ uses the Area Under the Curve (AUC)
--     technique to measure performance.
--
-- -   RegressionRMSE: A regression @MLModel@ uses the Root Mean Square
--     Error (RMSE) technique to measure performance. RMSE measures the
--     difference between predicted and actual values for a single
--     variable.
--
-- -   MulticlassAvgFScore: A multiclass @MLModel@ uses the F1 score
--     technique to measure performance.
--
-- For more information about performance metrics, please see the
-- <https://docs.aws.amazon.com/machine-learning/latest/dg Amazon Machine Learning Developer Guide>.
--
-- 'startedAt', 'getEvaluationResponse_startedAt' - The epoch time when Amazon Machine Learning marked the @Evaluation@ as
-- @INPROGRESS@. @StartedAt@ isn\'t available if the @Evaluation@ is in the
-- @PENDING@ state.
--
-- 'status', 'getEvaluationResponse_status' - The status of the evaluation. This element can have one of the following
-- values:
--
-- -   @PENDING@ - Amazon Machine Language (Amazon ML) submitted a request
--     to evaluate an @MLModel@.
--
-- -   @INPROGRESS@ - The evaluation is underway.
--
-- -   @FAILED@ - The request to evaluate an @MLModel@ did not run to
--     completion. It is not usable.
--
-- -   @COMPLETED@ - The evaluation process completed successfully.
--
-- -   @DELETED@ - The @Evaluation@ is marked as deleted. It is not usable.
--
-- 'httpStatus', 'getEvaluationResponse_httpStatus' - The response's http status code.
newGetEvaluationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetEvaluationResponse
newGetEvaluationResponse :: Int -> GetEvaluationResponse
newGetEvaluationResponse Int
pHttpStatus_ =
  GetEvaluationResponse'
    { $sel:computeTime:GetEvaluationResponse' :: Maybe Integer
computeTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:GetEvaluationResponse' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:createdByIamUser:GetEvaluationResponse' :: Maybe Text
createdByIamUser = forall a. Maybe a
Prelude.Nothing,
      $sel:evaluationDataSourceId:GetEvaluationResponse' :: Maybe Text
evaluationDataSourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:evaluationId:GetEvaluationResponse' :: Maybe Text
evaluationId = forall a. Maybe a
Prelude.Nothing,
      $sel:finishedAt:GetEvaluationResponse' :: Maybe POSIX
finishedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:inputDataLocationS3:GetEvaluationResponse' :: Maybe Text
inputDataLocationS3 = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:GetEvaluationResponse' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:logUri:GetEvaluationResponse' :: Maybe Text
logUri = forall a. Maybe a
Prelude.Nothing,
      $sel:mLModelId:GetEvaluationResponse' :: Maybe Text
mLModelId = forall a. Maybe a
Prelude.Nothing,
      $sel:message:GetEvaluationResponse' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetEvaluationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:performanceMetrics:GetEvaluationResponse' :: Maybe PerformanceMetrics
performanceMetrics = forall a. Maybe a
Prelude.Nothing,
      $sel:startedAt:GetEvaluationResponse' :: Maybe POSIX
startedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetEvaluationResponse' :: Maybe EntityStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetEvaluationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The approximate CPU time in milliseconds that Amazon Machine Learning
-- spent processing the @Evaluation@, normalized and scaled on computation
-- resources. @ComputeTime@ is only available if the @Evaluation@ is in the
-- @COMPLETED@ state.
getEvaluationResponse_computeTime :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Integer)
getEvaluationResponse_computeTime :: Lens' GetEvaluationResponse (Maybe Integer)
getEvaluationResponse_computeTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Integer
computeTime :: Maybe Integer
$sel:computeTime:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Integer
computeTime} -> Maybe Integer
computeTime) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Integer
a -> GetEvaluationResponse
s {$sel:computeTime:GetEvaluationResponse' :: Maybe Integer
computeTime = Maybe Integer
a} :: GetEvaluationResponse)

-- | The time that the @Evaluation@ was created. The time is expressed in
-- epoch time.
getEvaluationResponse_createdAt :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.UTCTime)
getEvaluationResponse_createdAt :: Lens' GetEvaluationResponse (Maybe UTCTime)
getEvaluationResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe POSIX
a -> GetEvaluationResponse
s {$sel:createdAt:GetEvaluationResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: GetEvaluationResponse) 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 AWS user account that invoked the evaluation. The account type can
-- be either an AWS root account or an AWS Identity and Access Management
-- (IAM) user account.
getEvaluationResponse_createdByIamUser :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_createdByIamUser :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_createdByIamUser = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
createdByIamUser :: Maybe Text
$sel:createdByIamUser:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
createdByIamUser} -> Maybe Text
createdByIamUser) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:createdByIamUser:GetEvaluationResponse' :: Maybe Text
createdByIamUser = Maybe Text
a} :: GetEvaluationResponse)

-- | The @DataSource@ used for this evaluation.
getEvaluationResponse_evaluationDataSourceId :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_evaluationDataSourceId :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_evaluationDataSourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
evaluationDataSourceId :: Maybe Text
$sel:evaluationDataSourceId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
evaluationDataSourceId} -> Maybe Text
evaluationDataSourceId) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:evaluationDataSourceId:GetEvaluationResponse' :: Maybe Text
evaluationDataSourceId = Maybe Text
a} :: GetEvaluationResponse)

-- | The evaluation ID which is same as the @EvaluationId@ in the request.
getEvaluationResponse_evaluationId :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_evaluationId :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_evaluationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
evaluationId :: Maybe Text
$sel:evaluationId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
evaluationId} -> Maybe Text
evaluationId) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:evaluationId:GetEvaluationResponse' :: Maybe Text
evaluationId = Maybe Text
a} :: GetEvaluationResponse)

-- | The epoch time when Amazon Machine Learning marked the @Evaluation@ as
-- @COMPLETED@ or @FAILED@. @FinishedAt@ is only available when the
-- @Evaluation@ is in the @COMPLETED@ or @FAILED@ state.
getEvaluationResponse_finishedAt :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.UTCTime)
getEvaluationResponse_finishedAt :: Lens' GetEvaluationResponse (Maybe UTCTime)
getEvaluationResponse_finishedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe POSIX
finishedAt :: Maybe POSIX
$sel:finishedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
finishedAt} -> Maybe POSIX
finishedAt) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe POSIX
a -> GetEvaluationResponse
s {$sel:finishedAt:GetEvaluationResponse' :: Maybe POSIX
finishedAt = Maybe POSIX
a} :: GetEvaluationResponse) 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 location of the data file or directory in Amazon Simple Storage
-- Service (Amazon S3).
getEvaluationResponse_inputDataLocationS3 :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_inputDataLocationS3 :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_inputDataLocationS3 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
inputDataLocationS3 :: Maybe Text
$sel:inputDataLocationS3:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
inputDataLocationS3} -> Maybe Text
inputDataLocationS3) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:inputDataLocationS3:GetEvaluationResponse' :: Maybe Text
inputDataLocationS3 = Maybe Text
a} :: GetEvaluationResponse)

-- | The time of the most recent edit to the @Evaluation@. The time is
-- expressed in epoch time.
getEvaluationResponse_lastUpdatedAt :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.UTCTime)
getEvaluationResponse_lastUpdatedAt :: Lens' GetEvaluationResponse (Maybe UTCTime)
getEvaluationResponse_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe POSIX
a -> GetEvaluationResponse
s {$sel:lastUpdatedAt:GetEvaluationResponse' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: GetEvaluationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A link to the file that contains logs of the @CreateEvaluation@
-- operation.
getEvaluationResponse_logUri :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_logUri :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_logUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
logUri :: Maybe Text
$sel:logUri:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
logUri} -> Maybe Text
logUri) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:logUri:GetEvaluationResponse' :: Maybe Text
logUri = Maybe Text
a} :: GetEvaluationResponse)

-- | The ID of the @MLModel@ that was the focus of the evaluation.
getEvaluationResponse_mLModelId :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_mLModelId :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_mLModelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
mLModelId :: Maybe Text
$sel:mLModelId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
mLModelId} -> Maybe Text
mLModelId) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:mLModelId:GetEvaluationResponse' :: Maybe Text
mLModelId = Maybe Text
a} :: GetEvaluationResponse)

-- | A description of the most recent details about evaluating the @MLModel@.
getEvaluationResponse_message :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_message :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
message :: Maybe Text
$sel:message:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
message} -> Maybe Text
message) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:message:GetEvaluationResponse' :: Maybe Text
message = Maybe Text
a} :: GetEvaluationResponse)

-- | A user-supplied name or description of the @Evaluation@.
getEvaluationResponse_name :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.Text)
getEvaluationResponse_name :: Lens' GetEvaluationResponse (Maybe Text)
getEvaluationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe Text
a -> GetEvaluationResponse
s {$sel:name:GetEvaluationResponse' :: Maybe Text
name = Maybe Text
a} :: GetEvaluationResponse)

-- | Measurements of how well the @MLModel@ performed using observations
-- referenced by the @DataSource@. One of the following metric is returned
-- based on the type of the @MLModel@:
--
-- -   BinaryAUC: A binary @MLModel@ uses the Area Under the Curve (AUC)
--     technique to measure performance.
--
-- -   RegressionRMSE: A regression @MLModel@ uses the Root Mean Square
--     Error (RMSE) technique to measure performance. RMSE measures the
--     difference between predicted and actual values for a single
--     variable.
--
-- -   MulticlassAvgFScore: A multiclass @MLModel@ uses the F1 score
--     technique to measure performance.
--
-- For more information about performance metrics, please see the
-- <https://docs.aws.amazon.com/machine-learning/latest/dg Amazon Machine Learning Developer Guide>.
getEvaluationResponse_performanceMetrics :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe PerformanceMetrics)
getEvaluationResponse_performanceMetrics :: Lens' GetEvaluationResponse (Maybe PerformanceMetrics)
getEvaluationResponse_performanceMetrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe PerformanceMetrics
performanceMetrics :: Maybe PerformanceMetrics
$sel:performanceMetrics:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe PerformanceMetrics
performanceMetrics} -> Maybe PerformanceMetrics
performanceMetrics) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe PerformanceMetrics
a -> GetEvaluationResponse
s {$sel:performanceMetrics:GetEvaluationResponse' :: Maybe PerformanceMetrics
performanceMetrics = Maybe PerformanceMetrics
a} :: GetEvaluationResponse)

-- | The epoch time when Amazon Machine Learning marked the @Evaluation@ as
-- @INPROGRESS@. @StartedAt@ isn\'t available if the @Evaluation@ is in the
-- @PENDING@ state.
getEvaluationResponse_startedAt :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe Prelude.UTCTime)
getEvaluationResponse_startedAt :: Lens' GetEvaluationResponse (Maybe UTCTime)
getEvaluationResponse_startedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe POSIX
startedAt :: Maybe POSIX
$sel:startedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
startedAt} -> Maybe POSIX
startedAt) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe POSIX
a -> GetEvaluationResponse
s {$sel:startedAt:GetEvaluationResponse' :: Maybe POSIX
startedAt = Maybe POSIX
a} :: GetEvaluationResponse) 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 status of the evaluation. This element can have one of the following
-- values:
--
-- -   @PENDING@ - Amazon Machine Language (Amazon ML) submitted a request
--     to evaluate an @MLModel@.
--
-- -   @INPROGRESS@ - The evaluation is underway.
--
-- -   @FAILED@ - The request to evaluate an @MLModel@ did not run to
--     completion. It is not usable.
--
-- -   @COMPLETED@ - The evaluation process completed successfully.
--
-- -   @DELETED@ - The @Evaluation@ is marked as deleted. It is not usable.
getEvaluationResponse_status :: Lens.Lens' GetEvaluationResponse (Prelude.Maybe EntityStatus)
getEvaluationResponse_status :: Lens' GetEvaluationResponse (Maybe EntityStatus)
getEvaluationResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEvaluationResponse' {Maybe EntityStatus
status :: Maybe EntityStatus
$sel:status:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe EntityStatus
status} -> Maybe EntityStatus
status) (\s :: GetEvaluationResponse
s@GetEvaluationResponse' {} Maybe EntityStatus
a -> GetEvaluationResponse
s {$sel:status:GetEvaluationResponse' :: Maybe EntityStatus
status = Maybe EntityStatus
a} :: GetEvaluationResponse)

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

instance Prelude.NFData GetEvaluationResponse where
  rnf :: GetEvaluationResponse -> ()
rnf GetEvaluationResponse' {Int
Maybe Integer
Maybe Text
Maybe POSIX
Maybe EntityStatus
Maybe PerformanceMetrics
httpStatus :: Int
status :: Maybe EntityStatus
startedAt :: Maybe POSIX
performanceMetrics :: Maybe PerformanceMetrics
name :: Maybe Text
message :: Maybe Text
mLModelId :: Maybe Text
logUri :: Maybe Text
lastUpdatedAt :: Maybe POSIX
inputDataLocationS3 :: Maybe Text
finishedAt :: Maybe POSIX
evaluationId :: Maybe Text
evaluationDataSourceId :: Maybe Text
createdByIamUser :: Maybe Text
createdAt :: Maybe POSIX
computeTime :: Maybe Integer
$sel:httpStatus:GetEvaluationResponse' :: GetEvaluationResponse -> Int
$sel:status:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe EntityStatus
$sel:startedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
$sel:performanceMetrics:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe PerformanceMetrics
$sel:name:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:message:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:mLModelId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:logUri:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:lastUpdatedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
$sel:inputDataLocationS3:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:finishedAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
$sel:evaluationId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:evaluationDataSourceId:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:createdByIamUser:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Text
$sel:createdAt:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe POSIX
$sel:computeTime:GetEvaluationResponse' :: GetEvaluationResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
computeTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdByIamUser
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
evaluationDataSourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
evaluationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
finishedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
inputDataLocationS3
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logUri
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
mLModelId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PerformanceMetrics
performanceMetrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EntityStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus