{-# 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.GetDataQualityRuleRecommendationRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the specified recommendation run that was used to generate rules.
module Amazonka.Glue.GetDataQualityRuleRecommendationRun
  ( -- * Creating a Request
    GetDataQualityRuleRecommendationRun (..),
    newGetDataQualityRuleRecommendationRun,

    -- * Request Lenses
    getDataQualityRuleRecommendationRun_runId,

    -- * Destructuring the Response
    GetDataQualityRuleRecommendationRunResponse (..),
    newGetDataQualityRuleRecommendationRunResponse,

    -- * Response Lenses
    getDataQualityRuleRecommendationRunResponse_completedOn,
    getDataQualityRuleRecommendationRunResponse_createdRulesetName,
    getDataQualityRuleRecommendationRunResponse_dataSource,
    getDataQualityRuleRecommendationRunResponse_errorString,
    getDataQualityRuleRecommendationRunResponse_executionTime,
    getDataQualityRuleRecommendationRunResponse_lastModifiedOn,
    getDataQualityRuleRecommendationRunResponse_numberOfWorkers,
    getDataQualityRuleRecommendationRunResponse_recommendedRuleset,
    getDataQualityRuleRecommendationRunResponse_role,
    getDataQualityRuleRecommendationRunResponse_runId,
    getDataQualityRuleRecommendationRunResponse_startedOn,
    getDataQualityRuleRecommendationRunResponse_status,
    getDataQualityRuleRecommendationRunResponse_timeout,
    getDataQualityRuleRecommendationRunResponse_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:/ 'newGetDataQualityRuleRecommendationRun' smart constructor.
data GetDataQualityRuleRecommendationRun = GetDataQualityRuleRecommendationRun'
  { -- | The unique run identifier associated with this run.
    GetDataQualityRuleRecommendationRun -> Text
runId :: Prelude.Text
  }
  deriving (GetDataQualityRuleRecommendationRun
-> GetDataQualityRuleRecommendationRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataQualityRuleRecommendationRun
-> GetDataQualityRuleRecommendationRun -> Bool
$c/= :: GetDataQualityRuleRecommendationRun
-> GetDataQualityRuleRecommendationRun -> Bool
== :: GetDataQualityRuleRecommendationRun
-> GetDataQualityRuleRecommendationRun -> Bool
$c== :: GetDataQualityRuleRecommendationRun
-> GetDataQualityRuleRecommendationRun -> Bool
Prelude.Eq, ReadPrec [GetDataQualityRuleRecommendationRun]
ReadPrec GetDataQualityRuleRecommendationRun
Int -> ReadS GetDataQualityRuleRecommendationRun
ReadS [GetDataQualityRuleRecommendationRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataQualityRuleRecommendationRun]
$creadListPrec :: ReadPrec [GetDataQualityRuleRecommendationRun]
readPrec :: ReadPrec GetDataQualityRuleRecommendationRun
$creadPrec :: ReadPrec GetDataQualityRuleRecommendationRun
readList :: ReadS [GetDataQualityRuleRecommendationRun]
$creadList :: ReadS [GetDataQualityRuleRecommendationRun]
readsPrec :: Int -> ReadS GetDataQualityRuleRecommendationRun
$creadsPrec :: Int -> ReadS GetDataQualityRuleRecommendationRun
Prelude.Read, Int -> GetDataQualityRuleRecommendationRun -> ShowS
[GetDataQualityRuleRecommendationRun] -> ShowS
GetDataQualityRuleRecommendationRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataQualityRuleRecommendationRun] -> ShowS
$cshowList :: [GetDataQualityRuleRecommendationRun] -> ShowS
show :: GetDataQualityRuleRecommendationRun -> String
$cshow :: GetDataQualityRuleRecommendationRun -> String
showsPrec :: Int -> GetDataQualityRuleRecommendationRun -> ShowS
$cshowsPrec :: Int -> GetDataQualityRuleRecommendationRun -> ShowS
Prelude.Show, forall x.
Rep GetDataQualityRuleRecommendationRun x
-> GetDataQualityRuleRecommendationRun
forall x.
GetDataQualityRuleRecommendationRun
-> Rep GetDataQualityRuleRecommendationRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataQualityRuleRecommendationRun x
-> GetDataQualityRuleRecommendationRun
$cfrom :: forall x.
GetDataQualityRuleRecommendationRun
-> Rep GetDataQualityRuleRecommendationRun x
Prelude.Generic)

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

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

instance
  Core.AWSRequest
    GetDataQualityRuleRecommendationRun
  where
  type
    AWSResponse GetDataQualityRuleRecommendationRun =
      GetDataQualityRuleRecommendationRunResponse
  request :: (Service -> Service)
-> GetDataQualityRuleRecommendationRun
-> Request GetDataQualityRuleRecommendationRun
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 GetDataQualityRuleRecommendationRun
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetDataQualityRuleRecommendationRun)))
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 Text
-> Maybe DataSource
-> Maybe Text
-> Maybe Int
-> Maybe POSIX
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe TaskStatusType
-> Maybe Natural
-> Int
-> GetDataQualityRuleRecommendationRunResponse
GetDataQualityRuleRecommendationRunResponse'
            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
"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
"CreatedRulesetName")
            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
"RecommendedRuleset")
            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
"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
    GetDataQualityRuleRecommendationRun
  where
  hashWithSalt :: Int -> GetDataQualityRuleRecommendationRun -> Int
hashWithSalt
    Int
_salt
    GetDataQualityRuleRecommendationRun' {Text
runId :: Text
$sel:runId:GetDataQualityRuleRecommendationRun' :: GetDataQualityRuleRecommendationRun -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
runId

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

instance
  Data.ToHeaders
    GetDataQualityRuleRecommendationRun
  where
  toHeaders :: GetDataQualityRuleRecommendationRun -> 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.GetDataQualityRuleRecommendationRun" ::
                          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
    GetDataQualityRuleRecommendationRun
  where
  toJSON :: GetDataQualityRuleRecommendationRun -> Value
toJSON GetDataQualityRuleRecommendationRun' {Text
runId :: Text
$sel:runId:GetDataQualityRuleRecommendationRun' :: GetDataQualityRuleRecommendationRun -> 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
    GetDataQualityRuleRecommendationRun
  where
  toPath :: GetDataQualityRuleRecommendationRun -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetDataQualityRuleRecommendationRunResponse' smart constructor.
data GetDataQualityRuleRecommendationRunResponse = GetDataQualityRuleRecommendationRunResponse'
  { -- | The date and time when this run was completed.
    GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
completedOn :: Prelude.Maybe Data.POSIX,
    -- | The name of the ruleset that was created by the run.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Text
createdRulesetName :: Prelude.Maybe Prelude.Text,
    -- | The data source (an Glue table) associated with this run.
    GetDataQualityRuleRecommendationRunResponse -> Maybe DataSource
dataSource :: Prelude.Maybe DataSource,
    -- | The error strings that are associated with the run.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Text
errorString :: Prelude.Maybe Prelude.Text,
    -- | The amount of time (in seconds) that the run consumed resources.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Int
executionTime :: Prelude.Maybe Prelude.Int,
    -- | A timestamp. The last point in time when this data quality rule
    -- recommendation run was modified.
    GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
lastModifiedOn :: Prelude.Maybe Data.POSIX,
    -- | The number of @G.1X@ workers to be used in the run. The default is 5.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | When a start rule recommendation run completes, it creates a recommended
    -- ruleset (a set of rules). This member has those rules in Data Quality
    -- Definition Language (DQDL) format.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Text
recommendedRuleset :: Prelude.Maybe Prelude.Text,
    -- | An IAM role supplied to encrypt the results of the run.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The unique run identifier associated with this run.
    GetDataQualityRuleRecommendationRunResponse -> Maybe Text
runId :: Prelude.Maybe Prelude.Text,
    -- | The date and time when this run started.
    GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
startedOn :: Prelude.Maybe Data.POSIX,
    -- | The status for this run.
    GetDataQualityRuleRecommendationRunResponse -> 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).
    GetDataQualityRuleRecommendationRunResponse -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    GetDataQualityRuleRecommendationRunResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDataQualityRuleRecommendationRunResponse
-> GetDataQualityRuleRecommendationRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataQualityRuleRecommendationRunResponse
-> GetDataQualityRuleRecommendationRunResponse -> Bool
$c/= :: GetDataQualityRuleRecommendationRunResponse
-> GetDataQualityRuleRecommendationRunResponse -> Bool
== :: GetDataQualityRuleRecommendationRunResponse
-> GetDataQualityRuleRecommendationRunResponse -> Bool
$c== :: GetDataQualityRuleRecommendationRunResponse
-> GetDataQualityRuleRecommendationRunResponse -> Bool
Prelude.Eq, ReadPrec [GetDataQualityRuleRecommendationRunResponse]
ReadPrec GetDataQualityRuleRecommendationRunResponse
Int -> ReadS GetDataQualityRuleRecommendationRunResponse
ReadS [GetDataQualityRuleRecommendationRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataQualityRuleRecommendationRunResponse]
$creadListPrec :: ReadPrec [GetDataQualityRuleRecommendationRunResponse]
readPrec :: ReadPrec GetDataQualityRuleRecommendationRunResponse
$creadPrec :: ReadPrec GetDataQualityRuleRecommendationRunResponse
readList :: ReadS [GetDataQualityRuleRecommendationRunResponse]
$creadList :: ReadS [GetDataQualityRuleRecommendationRunResponse]
readsPrec :: Int -> ReadS GetDataQualityRuleRecommendationRunResponse
$creadsPrec :: Int -> ReadS GetDataQualityRuleRecommendationRunResponse
Prelude.Read, Int -> GetDataQualityRuleRecommendationRunResponse -> ShowS
[GetDataQualityRuleRecommendationRunResponse] -> ShowS
GetDataQualityRuleRecommendationRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataQualityRuleRecommendationRunResponse] -> ShowS
$cshowList :: [GetDataQualityRuleRecommendationRunResponse] -> ShowS
show :: GetDataQualityRuleRecommendationRunResponse -> String
$cshow :: GetDataQualityRuleRecommendationRunResponse -> String
showsPrec :: Int -> GetDataQualityRuleRecommendationRunResponse -> ShowS
$cshowsPrec :: Int -> GetDataQualityRuleRecommendationRunResponse -> ShowS
Prelude.Show, forall x.
Rep GetDataQualityRuleRecommendationRunResponse x
-> GetDataQualityRuleRecommendationRunResponse
forall x.
GetDataQualityRuleRecommendationRunResponse
-> Rep GetDataQualityRuleRecommendationRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataQualityRuleRecommendationRunResponse x
-> GetDataQualityRuleRecommendationRunResponse
$cfrom :: forall x.
GetDataQualityRuleRecommendationRunResponse
-> Rep GetDataQualityRuleRecommendationRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDataQualityRuleRecommendationRunResponse' 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:
--
-- 'completedOn', 'getDataQualityRuleRecommendationRunResponse_completedOn' - The date and time when this run was completed.
--
-- 'createdRulesetName', 'getDataQualityRuleRecommendationRunResponse_createdRulesetName' - The name of the ruleset that was created by the run.
--
-- 'dataSource', 'getDataQualityRuleRecommendationRunResponse_dataSource' - The data source (an Glue table) associated with this run.
--
-- 'errorString', 'getDataQualityRuleRecommendationRunResponse_errorString' - The error strings that are associated with the run.
--
-- 'executionTime', 'getDataQualityRuleRecommendationRunResponse_executionTime' - The amount of time (in seconds) that the run consumed resources.
--
-- 'lastModifiedOn', 'getDataQualityRuleRecommendationRunResponse_lastModifiedOn' - A timestamp. The last point in time when this data quality rule
-- recommendation run was modified.
--
-- 'numberOfWorkers', 'getDataQualityRuleRecommendationRunResponse_numberOfWorkers' - The number of @G.1X@ workers to be used in the run. The default is 5.
--
-- 'recommendedRuleset', 'getDataQualityRuleRecommendationRunResponse_recommendedRuleset' - When a start rule recommendation run completes, it creates a recommended
-- ruleset (a set of rules). This member has those rules in Data Quality
-- Definition Language (DQDL) format.
--
-- 'role'', 'getDataQualityRuleRecommendationRunResponse_role' - An IAM role supplied to encrypt the results of the run.
--
-- 'runId', 'getDataQualityRuleRecommendationRunResponse_runId' - The unique run identifier associated with this run.
--
-- 'startedOn', 'getDataQualityRuleRecommendationRunResponse_startedOn' - The date and time when this run started.
--
-- 'status', 'getDataQualityRuleRecommendationRunResponse_status' - The status for this run.
--
-- 'timeout', 'getDataQualityRuleRecommendationRunResponse_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', 'getDataQualityRuleRecommendationRunResponse_httpStatus' - The response's http status code.
newGetDataQualityRuleRecommendationRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDataQualityRuleRecommendationRunResponse
newGetDataQualityRuleRecommendationRunResponse :: Int -> GetDataQualityRuleRecommendationRunResponse
newGetDataQualityRuleRecommendationRunResponse
  Int
pHttpStatus_ =
    GetDataQualityRuleRecommendationRunResponse'
      { $sel:completedOn:GetDataQualityRuleRecommendationRunResponse' :: Maybe POSIX
completedOn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:createdRulesetName:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
createdRulesetName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:dataSource:GetDataQualityRuleRecommendationRunResponse' :: Maybe DataSource
dataSource = forall a. Maybe a
Prelude.Nothing,
        $sel:errorString:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
errorString = forall a. Maybe a
Prelude.Nothing,
        $sel:executionTime:GetDataQualityRuleRecommendationRunResponse' :: Maybe Int
executionTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedOn:GetDataQualityRuleRecommendationRunResponse' :: Maybe POSIX
lastModifiedOn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:numberOfWorkers:GetDataQualityRuleRecommendationRunResponse' :: Maybe Int
numberOfWorkers =
          forall a. Maybe a
Prelude.Nothing,
        $sel:recommendedRuleset:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
recommendedRuleset =
          forall a. Maybe a
Prelude.Nothing,
        $sel:role':GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
        $sel:runId:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
        $sel:startedOn:GetDataQualityRuleRecommendationRunResponse' :: Maybe POSIX
startedOn = forall a. Maybe a
Prelude.Nothing,
        $sel:status:GetDataQualityRuleRecommendationRunResponse' :: Maybe TaskStatusType
status = forall a. Maybe a
Prelude.Nothing,
        $sel:timeout:GetDataQualityRuleRecommendationRunResponse' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetDataQualityRuleRecommendationRunResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The date and time when this run was completed.
getDataQualityRuleRecommendationRunResponse_completedOn :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.UTCTime)
getDataQualityRuleRecommendationRunResponse_completedOn :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe UTCTime)
getDataQualityRuleRecommendationRunResponse_completedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe POSIX
completedOn :: Maybe POSIX
$sel:completedOn:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
completedOn} -> Maybe POSIX
completedOn) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe POSIX
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:completedOn:GetDataQualityRuleRecommendationRunResponse' :: Maybe POSIX
completedOn = Maybe POSIX
a} :: GetDataQualityRuleRecommendationRunResponse) 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 name of the ruleset that was created by the run.
getDataQualityRuleRecommendationRunResponse_createdRulesetName :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.Text)
getDataQualityRuleRecommendationRunResponse_createdRulesetName :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe Text)
getDataQualityRuleRecommendationRunResponse_createdRulesetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe Text
createdRulesetName :: Maybe Text
$sel:createdRulesetName:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
createdRulesetName} -> Maybe Text
createdRulesetName) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe Text
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:createdRulesetName:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
createdRulesetName = Maybe Text
a} :: GetDataQualityRuleRecommendationRunResponse)

-- | The data source (an Glue table) associated with this run.
getDataQualityRuleRecommendationRunResponse_dataSource :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe DataSource)
getDataQualityRuleRecommendationRunResponse_dataSource :: Lens'
  GetDataQualityRuleRecommendationRunResponse (Maybe DataSource)
getDataQualityRuleRecommendationRunResponse_dataSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe DataSource
dataSource :: Maybe DataSource
$sel:dataSource:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe DataSource
dataSource} -> Maybe DataSource
dataSource) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe DataSource
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:dataSource:GetDataQualityRuleRecommendationRunResponse' :: Maybe DataSource
dataSource = Maybe DataSource
a} :: GetDataQualityRuleRecommendationRunResponse)

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

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

-- | A timestamp. The last point in time when this data quality rule
-- recommendation run was modified.
getDataQualityRuleRecommendationRunResponse_lastModifiedOn :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.UTCTime)
getDataQualityRuleRecommendationRunResponse_lastModifiedOn :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe UTCTime)
getDataQualityRuleRecommendationRunResponse_lastModifiedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe POSIX
lastModifiedOn :: Maybe POSIX
$sel:lastModifiedOn:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
lastModifiedOn} -> Maybe POSIX
lastModifiedOn) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe POSIX
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:lastModifiedOn:GetDataQualityRuleRecommendationRunResponse' :: Maybe POSIX
lastModifiedOn = Maybe POSIX
a} :: GetDataQualityRuleRecommendationRunResponse) 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.
getDataQualityRuleRecommendationRunResponse_numberOfWorkers :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.Int)
getDataQualityRuleRecommendationRunResponse_numberOfWorkers :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe Int)
getDataQualityRuleRecommendationRunResponse_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe Int
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:numberOfWorkers:GetDataQualityRuleRecommendationRunResponse' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: GetDataQualityRuleRecommendationRunResponse)

-- | When a start rule recommendation run completes, it creates a recommended
-- ruleset (a set of rules). This member has those rules in Data Quality
-- Definition Language (DQDL) format.
getDataQualityRuleRecommendationRunResponse_recommendedRuleset :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.Text)
getDataQualityRuleRecommendationRunResponse_recommendedRuleset :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe Text)
getDataQualityRuleRecommendationRunResponse_recommendedRuleset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe Text
recommendedRuleset :: Maybe Text
$sel:recommendedRuleset:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
recommendedRuleset} -> Maybe Text
recommendedRuleset) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe Text
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:recommendedRuleset:GetDataQualityRuleRecommendationRunResponse' :: Maybe Text
recommendedRuleset = Maybe Text
a} :: GetDataQualityRuleRecommendationRunResponse)

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

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

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

-- | 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).
getDataQualityRuleRecommendationRunResponse_timeout :: Lens.Lens' GetDataQualityRuleRecommendationRunResponse (Prelude.Maybe Prelude.Natural)
getDataQualityRuleRecommendationRunResponse_timeout :: Lens' GetDataQualityRuleRecommendationRunResponse (Maybe Natural)
getDataQualityRuleRecommendationRunResponse_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataQualityRuleRecommendationRunResponse' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: GetDataQualityRuleRecommendationRunResponse
s@GetDataQualityRuleRecommendationRunResponse' {} Maybe Natural
a -> GetDataQualityRuleRecommendationRunResponse
s {$sel:timeout:GetDataQualityRuleRecommendationRunResponse' :: Maybe Natural
timeout = Maybe Natural
a} :: GetDataQualityRuleRecommendationRunResponse)

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

instance
  Prelude.NFData
    GetDataQualityRuleRecommendationRunResponse
  where
  rnf :: GetDataQualityRuleRecommendationRunResponse -> ()
rnf GetDataQualityRuleRecommendationRunResponse' {Int
Maybe Int
Maybe Natural
Maybe Text
Maybe POSIX
Maybe DataSource
Maybe TaskStatusType
httpStatus :: Int
timeout :: Maybe Natural
status :: Maybe TaskStatusType
startedOn :: Maybe POSIX
runId :: Maybe Text
role' :: Maybe Text
recommendedRuleset :: Maybe Text
numberOfWorkers :: Maybe Int
lastModifiedOn :: Maybe POSIX
executionTime :: Maybe Int
errorString :: Maybe Text
dataSource :: Maybe DataSource
createdRulesetName :: Maybe Text
completedOn :: Maybe POSIX
$sel:httpStatus:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Int
$sel:timeout:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Natural
$sel:status:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe TaskStatusType
$sel:startedOn:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
$sel:runId:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
$sel:role':GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
$sel:recommendedRuleset:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
$sel:numberOfWorkers:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Int
$sel:lastModifiedOn:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
$sel:executionTime:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Int
$sel:errorString:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
$sel:dataSource:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe DataSource
$sel:createdRulesetName:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe Text
$sel:completedOn:GetDataQualityRuleRecommendationRunResponse' :: GetDataQualityRuleRecommendationRunResponse -> Maybe POSIX
..} =
    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 Text
createdRulesetName
      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 Text
recommendedRuleset
      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 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