{-# 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.Glue.GetDataQualityRulesetEvaluationRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a specific run where a ruleset is evaluated against a data
-- source.
module Amazonka.Glue.GetDataQualityRulesetEvaluationRun
  ( -- * Creating a Request
    GetDataQualityRulesetEvaluationRun (..),
    newGetDataQualityRulesetEvaluationRun,

    -- * Request Lenses
    getDataQualityRulesetEvaluationRun_runId,

    -- * Destructuring the Response
    GetDataQualityRulesetEvaluationRunResponse (..),
    newGetDataQualityRulesetEvaluationRunResponse,

    -- * Response Lenses
    getDataQualityRulesetEvaluationRunResponse_additionalRunOptions,
    getDataQualityRulesetEvaluationRunResponse_completedOn,
    getDataQualityRulesetEvaluationRunResponse_dataSource,
    getDataQualityRulesetEvaluationRunResponse_errorString,
    getDataQualityRulesetEvaluationRunResponse_executionTime,
    getDataQualityRulesetEvaluationRunResponse_lastModifiedOn,
    getDataQualityRulesetEvaluationRunResponse_numberOfWorkers,
    getDataQualityRulesetEvaluationRunResponse_resultIds,
    getDataQualityRulesetEvaluationRunResponse_role,
    getDataQualityRulesetEvaluationRunResponse_rulesetNames,
    getDataQualityRulesetEvaluationRunResponse_runId,
    getDataQualityRulesetEvaluationRunResponse_startedOn,
    getDataQualityRulesetEvaluationRunResponse_status,
    getDataQualityRulesetEvaluationRunResponse_timeout,
    getDataQualityRulesetEvaluationRunResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetDataQualityRulesetEvaluationRun' smart constructor.
data GetDataQualityRulesetEvaluationRun = GetDataQualityRulesetEvaluationRun'
  { -- | The unique run identifier associated with this run.
    GetDataQualityRulesetEvaluationRun -> Text
runId :: Prelude.Text
  }
  deriving (GetDataQualityRulesetEvaluationRun
-> GetDataQualityRulesetEvaluationRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataQualityRulesetEvaluationRun
-> GetDataQualityRulesetEvaluationRun -> Bool
$c/= :: GetDataQualityRulesetEvaluationRun
-> GetDataQualityRulesetEvaluationRun -> Bool
== :: GetDataQualityRulesetEvaluationRun
-> GetDataQualityRulesetEvaluationRun -> Bool
$c== :: GetDataQualityRulesetEvaluationRun
-> GetDataQualityRulesetEvaluationRun -> Bool
Prelude.Eq, ReadPrec [GetDataQualityRulesetEvaluationRun]
ReadPrec GetDataQualityRulesetEvaluationRun
Int -> ReadS GetDataQualityRulesetEvaluationRun
ReadS [GetDataQualityRulesetEvaluationRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataQualityRulesetEvaluationRun]
$creadListPrec :: ReadPrec [GetDataQualityRulesetEvaluationRun]
readPrec :: ReadPrec GetDataQualityRulesetEvaluationRun
$creadPrec :: ReadPrec GetDataQualityRulesetEvaluationRun
readList :: ReadS [GetDataQualityRulesetEvaluationRun]
$creadList :: ReadS [GetDataQualityRulesetEvaluationRun]
readsPrec :: Int -> ReadS GetDataQualityRulesetEvaluationRun
$creadsPrec :: Int -> ReadS GetDataQualityRulesetEvaluationRun
Prelude.Read, Int -> GetDataQualityRulesetEvaluationRun -> ShowS
[GetDataQualityRulesetEvaluationRun] -> ShowS
GetDataQualityRulesetEvaluationRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataQualityRulesetEvaluationRun] -> ShowS
$cshowList :: [GetDataQualityRulesetEvaluationRun] -> ShowS
show :: GetDataQualityRulesetEvaluationRun -> String
$cshow :: GetDataQualityRulesetEvaluationRun -> String
showsPrec :: Int -> GetDataQualityRulesetEvaluationRun -> ShowS
$cshowsPrec :: Int -> GetDataQualityRulesetEvaluationRun -> ShowS
Prelude.Show, forall x.
Rep GetDataQualityRulesetEvaluationRun x
-> GetDataQualityRulesetEvaluationRun
forall x.
GetDataQualityRulesetEvaluationRun
-> Rep GetDataQualityRulesetEvaluationRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataQualityRulesetEvaluationRun x
-> GetDataQualityRulesetEvaluationRun
$cfrom :: forall x.
GetDataQualityRulesetEvaluationRun
-> Rep GetDataQualityRulesetEvaluationRun x
Prelude.Generic)

-- |
-- Create a value of 'GetDataQualityRulesetEvaluationRun' 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:
--
-- 'runId', 'getDataQualityRulesetEvaluationRun_runId' - The unique run identifier associated with this run.
newGetDataQualityRulesetEvaluationRun ::
  -- | 'runId'
  Prelude.Text ->
  GetDataQualityRulesetEvaluationRun
newGetDataQualityRulesetEvaluationRun :: Text -> GetDataQualityRulesetEvaluationRun
newGetDataQualityRulesetEvaluationRun Text
pRunId_ =
  GetDataQualityRulesetEvaluationRun'
    { $sel:runId:GetDataQualityRulesetEvaluationRun' :: Text
runId =
        Text
pRunId_
    }

-- | The unique run identifier associated with this run.
getDataQualityRulesetEvaluationRun_runId :: Lens.Lens' GetDataQualityRulesetEvaluationRun Prelude.Text
getDataQualityRulesetEvaluationRun_runId :: Lens' GetDataQualityRulesetEvaluationRun Text
getDataQualityRulesetEvaluationRun_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRun' {Text
runId :: Text
$sel:runId:GetDataQualityRulesetEvaluationRun' :: GetDataQualityRulesetEvaluationRun -> Text
runId} -> Text
runId) (\s :: GetDataQualityRulesetEvaluationRun
s@GetDataQualityRulesetEvaluationRun' {} Text
a -> GetDataQualityRulesetEvaluationRun
s {$sel:runId:GetDataQualityRulesetEvaluationRun' :: Text
runId = Text
a} :: GetDataQualityRulesetEvaluationRun)

instance
  Core.AWSRequest
    GetDataQualityRulesetEvaluationRun
  where
  type
    AWSResponse GetDataQualityRulesetEvaluationRun =
      GetDataQualityRulesetEvaluationRunResponse
  request :: (Service -> Service)
-> GetDataQualityRulesetEvaluationRun
-> Request GetDataQualityRulesetEvaluationRun
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 GetDataQualityRulesetEvaluationRun
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetDataQualityRulesetEvaluationRun)))
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 DataQualityEvaluationRunAdditionalRunOptions
-> Maybe POSIX
-> Maybe DataSource
-> Maybe Text
-> Maybe Int
-> Maybe POSIX
-> Maybe Int
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe POSIX
-> Maybe TaskStatusType
-> Maybe Natural
-> Int
-> GetDataQualityRulesetEvaluationRunResponse
GetDataQualityRulesetEvaluationRunResponse'
            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
"AdditionalRunOptions")
            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
"CompletedOn")
            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
"DataSource")
            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
"ErrorString")
            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
"ExecutionTime")
            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
"LastModifiedOn")
            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
"NumberOfWorkers")
            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
"ResultIds")
            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
"Role")
            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
"RulesetNames")
            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
"RunId")
            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
"StartedOn")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Timeout")
            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
    GetDataQualityRulesetEvaluationRun
  where
  hashWithSalt :: Int -> GetDataQualityRulesetEvaluationRun -> Int
hashWithSalt
    Int
_salt
    GetDataQualityRulesetEvaluationRun' {Text
runId :: Text
$sel:runId:GetDataQualityRulesetEvaluationRun' :: GetDataQualityRulesetEvaluationRun -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
runId

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

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

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

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

-- | /See:/ 'newGetDataQualityRulesetEvaluationRunResponse' smart constructor.
data GetDataQualityRulesetEvaluationRunResponse = GetDataQualityRulesetEvaluationRunResponse'
  { -- | Additional run options you can specify for an evaluation run.
    GetDataQualityRulesetEvaluationRunResponse
-> Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions :: Prelude.Maybe DataQualityEvaluationRunAdditionalRunOptions,
    -- | The date and time when this run was completed.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
completedOn :: Prelude.Maybe Data.POSIX,
    -- | The data source (an Glue table) associated with this evaluation run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe DataSource
dataSource :: Prelude.Maybe DataSource,
    -- | The error strings that are associated with the run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
errorString :: Prelude.Maybe Prelude.Text,
    -- | The amount of time (in seconds) that the run consumed resources.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
executionTime :: Prelude.Maybe Prelude.Int,
    -- | A timestamp. The last point in time when this data quality rule
    -- recommendation run was modified.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
lastModifiedOn :: Prelude.Maybe Data.POSIX,
    -- | The number of @G.1X@ workers to be used in the run. The default is 5.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | A list of result IDs for the data quality results for the run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
resultIds :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | An IAM role supplied to encrypt the results of the run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | A list of ruleset names for the run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
rulesetNames :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The unique run identifier associated with this run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
runId :: Prelude.Maybe Prelude.Text,
    -- | The date and time when this run started.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
startedOn :: Prelude.Maybe Data.POSIX,
    -- | The status for this run.
    GetDataQualityRulesetEvaluationRunResponse -> Maybe TaskStatusType
status :: Prelude.Maybe TaskStatusType,
    -- | The timeout for a run in minutes. This is the maximum time that a run
    -- can consume resources before it is terminated and enters @TIMEOUT@
    -- status. The default is 2,880 minutes (48 hours).
    GetDataQualityRulesetEvaluationRunResponse -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    GetDataQualityRulesetEvaluationRunResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDataQualityRulesetEvaluationRunResponse
-> GetDataQualityRulesetEvaluationRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataQualityRulesetEvaluationRunResponse
-> GetDataQualityRulesetEvaluationRunResponse -> Bool
$c/= :: GetDataQualityRulesetEvaluationRunResponse
-> GetDataQualityRulesetEvaluationRunResponse -> Bool
== :: GetDataQualityRulesetEvaluationRunResponse
-> GetDataQualityRulesetEvaluationRunResponse -> Bool
$c== :: GetDataQualityRulesetEvaluationRunResponse
-> GetDataQualityRulesetEvaluationRunResponse -> Bool
Prelude.Eq, ReadPrec [GetDataQualityRulesetEvaluationRunResponse]
ReadPrec GetDataQualityRulesetEvaluationRunResponse
Int -> ReadS GetDataQualityRulesetEvaluationRunResponse
ReadS [GetDataQualityRulesetEvaluationRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataQualityRulesetEvaluationRunResponse]
$creadListPrec :: ReadPrec [GetDataQualityRulesetEvaluationRunResponse]
readPrec :: ReadPrec GetDataQualityRulesetEvaluationRunResponse
$creadPrec :: ReadPrec GetDataQualityRulesetEvaluationRunResponse
readList :: ReadS [GetDataQualityRulesetEvaluationRunResponse]
$creadList :: ReadS [GetDataQualityRulesetEvaluationRunResponse]
readsPrec :: Int -> ReadS GetDataQualityRulesetEvaluationRunResponse
$creadsPrec :: Int -> ReadS GetDataQualityRulesetEvaluationRunResponse
Prelude.Read, Int -> GetDataQualityRulesetEvaluationRunResponse -> ShowS
[GetDataQualityRulesetEvaluationRunResponse] -> ShowS
GetDataQualityRulesetEvaluationRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataQualityRulesetEvaluationRunResponse] -> ShowS
$cshowList :: [GetDataQualityRulesetEvaluationRunResponse] -> ShowS
show :: GetDataQualityRulesetEvaluationRunResponse -> String
$cshow :: GetDataQualityRulesetEvaluationRunResponse -> String
showsPrec :: Int -> GetDataQualityRulesetEvaluationRunResponse -> ShowS
$cshowsPrec :: Int -> GetDataQualityRulesetEvaluationRunResponse -> ShowS
Prelude.Show, forall x.
Rep GetDataQualityRulesetEvaluationRunResponse x
-> GetDataQualityRulesetEvaluationRunResponse
forall x.
GetDataQualityRulesetEvaluationRunResponse
-> Rep GetDataQualityRulesetEvaluationRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataQualityRulesetEvaluationRunResponse x
-> GetDataQualityRulesetEvaluationRunResponse
$cfrom :: forall x.
GetDataQualityRulesetEvaluationRunResponse
-> Rep GetDataQualityRulesetEvaluationRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDataQualityRulesetEvaluationRunResponse' 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:
--
-- 'additionalRunOptions', 'getDataQualityRulesetEvaluationRunResponse_additionalRunOptions' - Additional run options you can specify for an evaluation run.
--
-- 'completedOn', 'getDataQualityRulesetEvaluationRunResponse_completedOn' - The date and time when this run was completed.
--
-- 'dataSource', 'getDataQualityRulesetEvaluationRunResponse_dataSource' - The data source (an Glue table) associated with this evaluation run.
--
-- 'errorString', 'getDataQualityRulesetEvaluationRunResponse_errorString' - The error strings that are associated with the run.
--
-- 'executionTime', 'getDataQualityRulesetEvaluationRunResponse_executionTime' - The amount of time (in seconds) that the run consumed resources.
--
-- 'lastModifiedOn', 'getDataQualityRulesetEvaluationRunResponse_lastModifiedOn' - A timestamp. The last point in time when this data quality rule
-- recommendation run was modified.
--
-- 'numberOfWorkers', 'getDataQualityRulesetEvaluationRunResponse_numberOfWorkers' - The number of @G.1X@ workers to be used in the run. The default is 5.
--
-- 'resultIds', 'getDataQualityRulesetEvaluationRunResponse_resultIds' - A list of result IDs for the data quality results for the run.
--
-- 'role'', 'getDataQualityRulesetEvaluationRunResponse_role' - An IAM role supplied to encrypt the results of the run.
--
-- 'rulesetNames', 'getDataQualityRulesetEvaluationRunResponse_rulesetNames' - A list of ruleset names for the run.
--
-- 'runId', 'getDataQualityRulesetEvaluationRunResponse_runId' - The unique run identifier associated with this run.
--
-- 'startedOn', 'getDataQualityRulesetEvaluationRunResponse_startedOn' - The date and time when this run started.
--
-- 'status', 'getDataQualityRulesetEvaluationRunResponse_status' - The status for this run.
--
-- 'timeout', 'getDataQualityRulesetEvaluationRunResponse_timeout' - The timeout for a run in minutes. This is the maximum time that a run
-- can consume resources before it is terminated and enters @TIMEOUT@
-- status. The default is 2,880 minutes (48 hours).
--
-- 'httpStatus', 'getDataQualityRulesetEvaluationRunResponse_httpStatus' - The response's http status code.
newGetDataQualityRulesetEvaluationRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDataQualityRulesetEvaluationRunResponse
newGetDataQualityRulesetEvaluationRunResponse :: Int -> GetDataQualityRulesetEvaluationRunResponse
newGetDataQualityRulesetEvaluationRunResponse
  Int
pHttpStatus_ =
    GetDataQualityRulesetEvaluationRunResponse'
      { $sel:additionalRunOptions:GetDataQualityRulesetEvaluationRunResponse' :: Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions =
          forall a. Maybe a
Prelude.Nothing,
        $sel:completedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
completedOn = forall a. Maybe a
Prelude.Nothing,
        $sel:dataSource:GetDataQualityRulesetEvaluationRunResponse' :: Maybe DataSource
dataSource = forall a. Maybe a
Prelude.Nothing,
        $sel:errorString:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
errorString = forall a. Maybe a
Prelude.Nothing,
        $sel:executionTime:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Int
executionTime = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
lastModifiedOn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:numberOfWorkers:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Int
numberOfWorkers =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resultIds:GetDataQualityRulesetEvaluationRunResponse' :: Maybe (NonEmpty Text)
resultIds = forall a. Maybe a
Prelude.Nothing,
        $sel:role':GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
        $sel:rulesetNames:GetDataQualityRulesetEvaluationRunResponse' :: Maybe (NonEmpty Text)
rulesetNames = forall a. Maybe a
Prelude.Nothing,
        $sel:runId:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
        $sel:startedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
startedOn = forall a. Maybe a
Prelude.Nothing,
        $sel:status:GetDataQualityRulesetEvaluationRunResponse' :: Maybe TaskStatusType
status = forall a. Maybe a
Prelude.Nothing,
        $sel:timeout:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetDataQualityRulesetEvaluationRunResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Additional run options you can specify for an evaluation run.
getDataQualityRulesetEvaluationRunResponse_additionalRunOptions :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe DataQualityEvaluationRunAdditionalRunOptions)
getDataQualityRulesetEvaluationRunResponse_additionalRunOptions :: Lens'
  GetDataQualityRulesetEvaluationRunResponse
  (Maybe DataQualityEvaluationRunAdditionalRunOptions)
getDataQualityRulesetEvaluationRunResponse_additionalRunOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions :: Maybe DataQualityEvaluationRunAdditionalRunOptions
$sel:additionalRunOptions:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse
-> Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions} -> Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe DataQualityEvaluationRunAdditionalRunOptions
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:additionalRunOptions:GetDataQualityRulesetEvaluationRunResponse' :: Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions = Maybe DataQualityEvaluationRunAdditionalRunOptions
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | The date and time when this run was completed.
getDataQualityRulesetEvaluationRunResponse_completedOn :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.UTCTime)
getDataQualityRulesetEvaluationRunResponse_completedOn :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe UTCTime)
getDataQualityRulesetEvaluationRunResponse_completedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe POSIX
completedOn :: Maybe POSIX
$sel:completedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
completedOn} -> Maybe POSIX
completedOn) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe POSIX
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:completedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
completedOn = Maybe POSIX
a} :: GetDataQualityRulesetEvaluationRunResponse) 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 data source (an Glue table) associated with this evaluation run.
getDataQualityRulesetEvaluationRunResponse_dataSource :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe DataSource)
getDataQualityRulesetEvaluationRunResponse_dataSource :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe DataSource)
getDataQualityRulesetEvaluationRunResponse_dataSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe DataSource
dataSource :: Maybe DataSource
$sel:dataSource:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe DataSource
dataSource} -> Maybe DataSource
dataSource) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe DataSource
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:dataSource:GetDataQualityRulesetEvaluationRunResponse' :: Maybe DataSource
dataSource = Maybe DataSource
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | The error strings that are associated with the run.
getDataQualityRulesetEvaluationRunResponse_errorString :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Text)
getDataQualityRulesetEvaluationRunResponse_errorString :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Text)
getDataQualityRulesetEvaluationRunResponse_errorString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Text
errorString :: Maybe Text
$sel:errorString:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
errorString} -> Maybe Text
errorString) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Text
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:errorString:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
errorString = Maybe Text
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | The amount of time (in seconds) that the run consumed resources.
getDataQualityRulesetEvaluationRunResponse_executionTime :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Int)
getDataQualityRulesetEvaluationRunResponse_executionTime :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Int)
getDataQualityRulesetEvaluationRunResponse_executionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Int
executionTime :: Maybe Int
$sel:executionTime:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
executionTime} -> Maybe Int
executionTime) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Int
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:executionTime:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Int
executionTime = Maybe Int
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | A timestamp. The last point in time when this data quality rule
-- recommendation run was modified.
getDataQualityRulesetEvaluationRunResponse_lastModifiedOn :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.UTCTime)
getDataQualityRulesetEvaluationRunResponse_lastModifiedOn :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe UTCTime)
getDataQualityRulesetEvaluationRunResponse_lastModifiedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe POSIX
lastModifiedOn :: Maybe POSIX
$sel:lastModifiedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
lastModifiedOn} -> Maybe POSIX
lastModifiedOn) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe POSIX
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:lastModifiedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
lastModifiedOn = Maybe POSIX
a} :: GetDataQualityRulesetEvaluationRunResponse) 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 @G.1X@ workers to be used in the run. The default is 5.
getDataQualityRulesetEvaluationRunResponse_numberOfWorkers :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Int)
getDataQualityRulesetEvaluationRunResponse_numberOfWorkers :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Int)
getDataQualityRulesetEvaluationRunResponse_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Int
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:numberOfWorkers:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | A list of result IDs for the data quality results for the run.
getDataQualityRulesetEvaluationRunResponse_resultIds :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
getDataQualityRulesetEvaluationRunResponse_resultIds :: Lens'
  GetDataQualityRulesetEvaluationRunResponse (Maybe (NonEmpty Text))
getDataQualityRulesetEvaluationRunResponse_resultIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe (NonEmpty Text)
resultIds :: Maybe (NonEmpty Text)
$sel:resultIds:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
resultIds} -> Maybe (NonEmpty Text)
resultIds) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe (NonEmpty Text)
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:resultIds:GetDataQualityRulesetEvaluationRunResponse' :: Maybe (NonEmpty Text)
resultIds = Maybe (NonEmpty Text)
a} :: GetDataQualityRulesetEvaluationRunResponse) 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

-- | An IAM role supplied to encrypt the results of the run.
getDataQualityRulesetEvaluationRunResponse_role :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Text)
getDataQualityRulesetEvaluationRunResponse_role :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Text)
getDataQualityRulesetEvaluationRunResponse_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Text
role' :: Maybe Text
$sel:role':GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
role'} -> Maybe Text
role') (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Text
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:role':GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
role' = Maybe Text
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | A list of ruleset names for the run.
getDataQualityRulesetEvaluationRunResponse_rulesetNames :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
getDataQualityRulesetEvaluationRunResponse_rulesetNames :: Lens'
  GetDataQualityRulesetEvaluationRunResponse (Maybe (NonEmpty Text))
getDataQualityRulesetEvaluationRunResponse_rulesetNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe (NonEmpty Text)
rulesetNames :: Maybe (NonEmpty Text)
$sel:rulesetNames:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
rulesetNames} -> Maybe (NonEmpty Text)
rulesetNames) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe (NonEmpty Text)
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:rulesetNames:GetDataQualityRulesetEvaluationRunResponse' :: Maybe (NonEmpty Text)
rulesetNames = Maybe (NonEmpty Text)
a} :: GetDataQualityRulesetEvaluationRunResponse) 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 unique run identifier associated with this run.
getDataQualityRulesetEvaluationRunResponse_runId :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Text)
getDataQualityRulesetEvaluationRunResponse_runId :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Text)
getDataQualityRulesetEvaluationRunResponse_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Text
runId :: Maybe Text
$sel:runId:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
runId} -> Maybe Text
runId) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Text
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:runId:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Text
runId = Maybe Text
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | The date and time when this run started.
getDataQualityRulesetEvaluationRunResponse_startedOn :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.UTCTime)
getDataQualityRulesetEvaluationRunResponse_startedOn :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe UTCTime)
getDataQualityRulesetEvaluationRunResponse_startedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe POSIX
startedOn :: Maybe POSIX
$sel:startedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
startedOn} -> Maybe POSIX
startedOn) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe POSIX
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:startedOn:GetDataQualityRulesetEvaluationRunResponse' :: Maybe POSIX
startedOn = Maybe POSIX
a} :: GetDataQualityRulesetEvaluationRunResponse) 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 for this run.
getDataQualityRulesetEvaluationRunResponse_status :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe TaskStatusType)
getDataQualityRulesetEvaluationRunResponse_status :: Lens'
  GetDataQualityRulesetEvaluationRunResponse (Maybe TaskStatusType)
getDataQualityRulesetEvaluationRunResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe TaskStatusType
status :: Maybe TaskStatusType
$sel:status:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe TaskStatusType
status} -> Maybe TaskStatusType
status) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe TaskStatusType
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:status:GetDataQualityRulesetEvaluationRunResponse' :: Maybe TaskStatusType
status = Maybe TaskStatusType
a} :: GetDataQualityRulesetEvaluationRunResponse)

-- | The timeout for a run in minutes. This is the maximum time that a run
-- can consume resources before it is terminated and enters @TIMEOUT@
-- status. The default is 2,880 minutes (48 hours).
getDataQualityRulesetEvaluationRunResponse_timeout :: Lens.Lens' GetDataQualityRulesetEvaluationRunResponse (Prelude.Maybe Prelude.Natural)
getDataQualityRulesetEvaluationRunResponse_timeout :: Lens' GetDataQualityRulesetEvaluationRunResponse (Maybe Natural)
getDataQualityRulesetEvaluationRunResponse_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRulesetEvaluationRunResponse' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: GetDataQualityRulesetEvaluationRunResponse
s@GetDataQualityRulesetEvaluationRunResponse' {} Maybe Natural
a -> GetDataQualityRulesetEvaluationRunResponse
s {$sel:timeout:GetDataQualityRulesetEvaluationRunResponse' :: Maybe Natural
timeout = Maybe Natural
a} :: GetDataQualityRulesetEvaluationRunResponse)

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

instance
  Prelude.NFData
    GetDataQualityRulesetEvaluationRunResponse
  where
  rnf :: GetDataQualityRulesetEvaluationRunResponse -> ()
rnf GetDataQualityRulesetEvaluationRunResponse' {Int
Maybe Int
Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe DataQualityEvaluationRunAdditionalRunOptions
Maybe DataSource
Maybe TaskStatusType
httpStatus :: Int
timeout :: Maybe Natural
status :: Maybe TaskStatusType
startedOn :: Maybe POSIX
runId :: Maybe Text
rulesetNames :: Maybe (NonEmpty Text)
role' :: Maybe Text
resultIds :: Maybe (NonEmpty Text)
numberOfWorkers :: Maybe Int
lastModifiedOn :: Maybe POSIX
executionTime :: Maybe Int
errorString :: Maybe Text
dataSource :: Maybe DataSource
completedOn :: Maybe POSIX
additionalRunOptions :: Maybe DataQualityEvaluationRunAdditionalRunOptions
$sel:httpStatus:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Int
$sel:timeout:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Natural
$sel:status:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe TaskStatusType
$sel:startedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
$sel:runId:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
$sel:rulesetNames:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
$sel:role':GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
$sel:resultIds:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe (NonEmpty Text)
$sel:numberOfWorkers:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
$sel:lastModifiedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
$sel:executionTime:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Int
$sel:errorString:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe Text
$sel:dataSource:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe DataSource
$sel:completedOn:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse -> Maybe POSIX
$sel:additionalRunOptions:GetDataQualityRulesetEvaluationRunResponse' :: GetDataQualityRulesetEvaluationRunResponse
-> Maybe DataQualityEvaluationRunAdditionalRunOptions
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DataQualityEvaluationRunAdditionalRunOptions
additionalRunOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSource
dataSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorString
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
executionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
resultIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
rulesetNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
runId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TaskStatusType
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus