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

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

-- |
-- Module      : Amazonka.SageMaker.Types.ClarifyCheckStepMetadata
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SageMaker.Types.ClarifyCheckStepMetadata where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The container for the metadata for the ClarifyCheck step. For more
-- information, see the topic on
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/build-and-manage-steps.html#step-type-clarify-check ClarifyCheck step>
-- in the /Amazon SageMaker Developer Guide/.
--
-- /See:/ 'newClarifyCheckStepMetadata' smart constructor.
data ClarifyCheckStepMetadata = ClarifyCheckStepMetadata'
  { -- | The Amazon S3 URI of baseline constraints file to be used for the drift
    -- check.
    ClarifyCheckStepMetadata -> Maybe Text
baselineUsedForDriftCheckConstraints :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 URI of the newly calculated baseline constraints file.
    ClarifyCheckStepMetadata -> Maybe Text
calculatedBaselineConstraints :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the check processing job that was run
    -- by this step\'s execution.
    ClarifyCheckStepMetadata -> Maybe Text
checkJobArn :: Prelude.Maybe Prelude.Text,
    -- | The type of the Clarify Check step
    ClarifyCheckStepMetadata -> Maybe Text
checkType :: Prelude.Maybe Prelude.Text,
    -- | The model package group name.
    ClarifyCheckStepMetadata -> Maybe Text
modelPackageGroupName :: Prelude.Maybe Prelude.Text,
    -- | This flag indicates if a newly calculated baseline can be accessed
    -- through step properties @BaselineUsedForDriftCheckConstraints@ and
    -- @BaselineUsedForDriftCheckStatistics@. If it is set to @False@, the
    -- previous baseline of the configured check type must also be available.
    -- These can be accessed through the @BaselineUsedForDriftCheckConstraints@
    -- property.
    ClarifyCheckStepMetadata -> Maybe Bool
registerNewBaseline :: Prelude.Maybe Prelude.Bool,
    -- | This flag indicates if the drift check against the previous baseline
    -- will be skipped or not. If it is set to @False@, the previous baseline
    -- of the configured check type must be available.
    ClarifyCheckStepMetadata -> Maybe Bool
skipCheck :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon S3 URI of the violation report if violations are detected.
    ClarifyCheckStepMetadata -> Maybe Text
violationReport :: Prelude.Maybe Prelude.Text
  }
  deriving (ClarifyCheckStepMetadata -> ClarifyCheckStepMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClarifyCheckStepMetadata -> ClarifyCheckStepMetadata -> Bool
$c/= :: ClarifyCheckStepMetadata -> ClarifyCheckStepMetadata -> Bool
== :: ClarifyCheckStepMetadata -> ClarifyCheckStepMetadata -> Bool
$c== :: ClarifyCheckStepMetadata -> ClarifyCheckStepMetadata -> Bool
Prelude.Eq, ReadPrec [ClarifyCheckStepMetadata]
ReadPrec ClarifyCheckStepMetadata
Int -> ReadS ClarifyCheckStepMetadata
ReadS [ClarifyCheckStepMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClarifyCheckStepMetadata]
$creadListPrec :: ReadPrec [ClarifyCheckStepMetadata]
readPrec :: ReadPrec ClarifyCheckStepMetadata
$creadPrec :: ReadPrec ClarifyCheckStepMetadata
readList :: ReadS [ClarifyCheckStepMetadata]
$creadList :: ReadS [ClarifyCheckStepMetadata]
readsPrec :: Int -> ReadS ClarifyCheckStepMetadata
$creadsPrec :: Int -> ReadS ClarifyCheckStepMetadata
Prelude.Read, Int -> ClarifyCheckStepMetadata -> ShowS
[ClarifyCheckStepMetadata] -> ShowS
ClarifyCheckStepMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClarifyCheckStepMetadata] -> ShowS
$cshowList :: [ClarifyCheckStepMetadata] -> ShowS
show :: ClarifyCheckStepMetadata -> String
$cshow :: ClarifyCheckStepMetadata -> String
showsPrec :: Int -> ClarifyCheckStepMetadata -> ShowS
$cshowsPrec :: Int -> ClarifyCheckStepMetadata -> ShowS
Prelude.Show, forall x.
Rep ClarifyCheckStepMetadata x -> ClarifyCheckStepMetadata
forall x.
ClarifyCheckStepMetadata -> Rep ClarifyCheckStepMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ClarifyCheckStepMetadata x -> ClarifyCheckStepMetadata
$cfrom :: forall x.
ClarifyCheckStepMetadata -> Rep ClarifyCheckStepMetadata x
Prelude.Generic)

-- |
-- Create a value of 'ClarifyCheckStepMetadata' 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:
--
-- 'baselineUsedForDriftCheckConstraints', 'clarifyCheckStepMetadata_baselineUsedForDriftCheckConstraints' - The Amazon S3 URI of baseline constraints file to be used for the drift
-- check.
--
-- 'calculatedBaselineConstraints', 'clarifyCheckStepMetadata_calculatedBaselineConstraints' - The Amazon S3 URI of the newly calculated baseline constraints file.
--
-- 'checkJobArn', 'clarifyCheckStepMetadata_checkJobArn' - The Amazon Resource Name (ARN) of the check processing job that was run
-- by this step\'s execution.
--
-- 'checkType', 'clarifyCheckStepMetadata_checkType' - The type of the Clarify Check step
--
-- 'modelPackageGroupName', 'clarifyCheckStepMetadata_modelPackageGroupName' - The model package group name.
--
-- 'registerNewBaseline', 'clarifyCheckStepMetadata_registerNewBaseline' - This flag indicates if a newly calculated baseline can be accessed
-- through step properties @BaselineUsedForDriftCheckConstraints@ and
-- @BaselineUsedForDriftCheckStatistics@. If it is set to @False@, the
-- previous baseline of the configured check type must also be available.
-- These can be accessed through the @BaselineUsedForDriftCheckConstraints@
-- property.
--
-- 'skipCheck', 'clarifyCheckStepMetadata_skipCheck' - This flag indicates if the drift check against the previous baseline
-- will be skipped or not. If it is set to @False@, the previous baseline
-- of the configured check type must be available.
--
-- 'violationReport', 'clarifyCheckStepMetadata_violationReport' - The Amazon S3 URI of the violation report if violations are detected.
newClarifyCheckStepMetadata ::
  ClarifyCheckStepMetadata
newClarifyCheckStepMetadata :: ClarifyCheckStepMetadata
newClarifyCheckStepMetadata =
  ClarifyCheckStepMetadata'
    { $sel:baselineUsedForDriftCheckConstraints:ClarifyCheckStepMetadata' :: Maybe Text
baselineUsedForDriftCheckConstraints =
        forall a. Maybe a
Prelude.Nothing,
      $sel:calculatedBaselineConstraints:ClarifyCheckStepMetadata' :: Maybe Text
calculatedBaselineConstraints = forall a. Maybe a
Prelude.Nothing,
      $sel:checkJobArn:ClarifyCheckStepMetadata' :: Maybe Text
checkJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:checkType:ClarifyCheckStepMetadata' :: Maybe Text
checkType = forall a. Maybe a
Prelude.Nothing,
      $sel:modelPackageGroupName:ClarifyCheckStepMetadata' :: Maybe Text
modelPackageGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:registerNewBaseline:ClarifyCheckStepMetadata' :: Maybe Bool
registerNewBaseline = forall a. Maybe a
Prelude.Nothing,
      $sel:skipCheck:ClarifyCheckStepMetadata' :: Maybe Bool
skipCheck = forall a. Maybe a
Prelude.Nothing,
      $sel:violationReport:ClarifyCheckStepMetadata' :: Maybe Text
violationReport = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon S3 URI of baseline constraints file to be used for the drift
-- check.
clarifyCheckStepMetadata_baselineUsedForDriftCheckConstraints :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_baselineUsedForDriftCheckConstraints :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_baselineUsedForDriftCheckConstraints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
baselineUsedForDriftCheckConstraints :: Maybe Text
$sel:baselineUsedForDriftCheckConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
baselineUsedForDriftCheckConstraints} -> Maybe Text
baselineUsedForDriftCheckConstraints) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:baselineUsedForDriftCheckConstraints:ClarifyCheckStepMetadata' :: Maybe Text
baselineUsedForDriftCheckConstraints = Maybe Text
a} :: ClarifyCheckStepMetadata)

-- | The Amazon S3 URI of the newly calculated baseline constraints file.
clarifyCheckStepMetadata_calculatedBaselineConstraints :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_calculatedBaselineConstraints :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_calculatedBaselineConstraints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
calculatedBaselineConstraints :: Maybe Text
$sel:calculatedBaselineConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
calculatedBaselineConstraints} -> Maybe Text
calculatedBaselineConstraints) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:calculatedBaselineConstraints:ClarifyCheckStepMetadata' :: Maybe Text
calculatedBaselineConstraints = Maybe Text
a} :: ClarifyCheckStepMetadata)

-- | The Amazon Resource Name (ARN) of the check processing job that was run
-- by this step\'s execution.
clarifyCheckStepMetadata_checkJobArn :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_checkJobArn :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_checkJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
checkJobArn :: Maybe Text
$sel:checkJobArn:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
checkJobArn} -> Maybe Text
checkJobArn) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:checkJobArn:ClarifyCheckStepMetadata' :: Maybe Text
checkJobArn = Maybe Text
a} :: ClarifyCheckStepMetadata)

-- | The type of the Clarify Check step
clarifyCheckStepMetadata_checkType :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_checkType :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_checkType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
checkType :: Maybe Text
$sel:checkType:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
checkType} -> Maybe Text
checkType) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:checkType:ClarifyCheckStepMetadata' :: Maybe Text
checkType = Maybe Text
a} :: ClarifyCheckStepMetadata)

-- | The model package group name.
clarifyCheckStepMetadata_modelPackageGroupName :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_modelPackageGroupName :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_modelPackageGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
modelPackageGroupName :: Maybe Text
$sel:modelPackageGroupName:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
modelPackageGroupName} -> Maybe Text
modelPackageGroupName) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:modelPackageGroupName:ClarifyCheckStepMetadata' :: Maybe Text
modelPackageGroupName = Maybe Text
a} :: ClarifyCheckStepMetadata)

-- | This flag indicates if a newly calculated baseline can be accessed
-- through step properties @BaselineUsedForDriftCheckConstraints@ and
-- @BaselineUsedForDriftCheckStatistics@. If it is set to @False@, the
-- previous baseline of the configured check type must also be available.
-- These can be accessed through the @BaselineUsedForDriftCheckConstraints@
-- property.
clarifyCheckStepMetadata_registerNewBaseline :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Bool)
clarifyCheckStepMetadata_registerNewBaseline :: Lens' ClarifyCheckStepMetadata (Maybe Bool)
clarifyCheckStepMetadata_registerNewBaseline = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Bool
registerNewBaseline :: Maybe Bool
$sel:registerNewBaseline:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
registerNewBaseline} -> Maybe Bool
registerNewBaseline) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Bool
a -> ClarifyCheckStepMetadata
s {$sel:registerNewBaseline:ClarifyCheckStepMetadata' :: Maybe Bool
registerNewBaseline = Maybe Bool
a} :: ClarifyCheckStepMetadata)

-- | This flag indicates if the drift check against the previous baseline
-- will be skipped or not. If it is set to @False@, the previous baseline
-- of the configured check type must be available.
clarifyCheckStepMetadata_skipCheck :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Bool)
clarifyCheckStepMetadata_skipCheck :: Lens' ClarifyCheckStepMetadata (Maybe Bool)
clarifyCheckStepMetadata_skipCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Bool
skipCheck :: Maybe Bool
$sel:skipCheck:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
skipCheck} -> Maybe Bool
skipCheck) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Bool
a -> ClarifyCheckStepMetadata
s {$sel:skipCheck:ClarifyCheckStepMetadata' :: Maybe Bool
skipCheck = Maybe Bool
a} :: ClarifyCheckStepMetadata)

-- | The Amazon S3 URI of the violation report if violations are detected.
clarifyCheckStepMetadata_violationReport :: Lens.Lens' ClarifyCheckStepMetadata (Prelude.Maybe Prelude.Text)
clarifyCheckStepMetadata_violationReport :: Lens' ClarifyCheckStepMetadata (Maybe Text)
clarifyCheckStepMetadata_violationReport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClarifyCheckStepMetadata' {Maybe Text
violationReport :: Maybe Text
$sel:violationReport:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
violationReport} -> Maybe Text
violationReport) (\s :: ClarifyCheckStepMetadata
s@ClarifyCheckStepMetadata' {} Maybe Text
a -> ClarifyCheckStepMetadata
s {$sel:violationReport:ClarifyCheckStepMetadata' :: Maybe Text
violationReport = Maybe Text
a} :: ClarifyCheckStepMetadata)

instance Data.FromJSON ClarifyCheckStepMetadata where
  parseJSON :: Value -> Parser ClarifyCheckStepMetadata
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ClarifyCheckStepMetadata"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> ClarifyCheckStepMetadata
ClarifyCheckStepMetadata'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BaselineUsedForDriftCheckConstraints")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CalculatedBaselineConstraints")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CheckJobArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CheckType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ModelPackageGroupName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RegisterNewBaseline")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SkipCheck")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ViolationReport")
      )

instance Prelude.Hashable ClarifyCheckStepMetadata where
  hashWithSalt :: Int -> ClarifyCheckStepMetadata -> Int
hashWithSalt Int
_salt ClarifyCheckStepMetadata' {Maybe Bool
Maybe Text
violationReport :: Maybe Text
skipCheck :: Maybe Bool
registerNewBaseline :: Maybe Bool
modelPackageGroupName :: Maybe Text
checkType :: Maybe Text
checkJobArn :: Maybe Text
calculatedBaselineConstraints :: Maybe Text
baselineUsedForDriftCheckConstraints :: Maybe Text
$sel:violationReport:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:skipCheck:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
$sel:registerNewBaseline:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
$sel:modelPackageGroupName:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:checkType:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:checkJobArn:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:calculatedBaselineConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:baselineUsedForDriftCheckConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baselineUsedForDriftCheckConstraints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
calculatedBaselineConstraints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
checkJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
checkType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
modelPackageGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
registerNewBaseline
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
skipCheck
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
violationReport

instance Prelude.NFData ClarifyCheckStepMetadata where
  rnf :: ClarifyCheckStepMetadata -> ()
rnf ClarifyCheckStepMetadata' {Maybe Bool
Maybe Text
violationReport :: Maybe Text
skipCheck :: Maybe Bool
registerNewBaseline :: Maybe Bool
modelPackageGroupName :: Maybe Text
checkType :: Maybe Text
checkJobArn :: Maybe Text
calculatedBaselineConstraints :: Maybe Text
baselineUsedForDriftCheckConstraints :: Maybe Text
$sel:violationReport:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:skipCheck:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
$sel:registerNewBaseline:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Bool
$sel:modelPackageGroupName:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:checkType:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:checkJobArn:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:calculatedBaselineConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
$sel:baselineUsedForDriftCheckConstraints:ClarifyCheckStepMetadata' :: ClarifyCheckStepMetadata -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baselineUsedForDriftCheckConstraints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
calculatedBaselineConstraints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
checkJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
checkType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelPackageGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
registerNewBaseline
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
skipCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
violationReport